{-# 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.Utxorpc.V1alpha.Sync.Sync (
SyncService(..), AnyChainBlock(), AnyChainBlock'Chain(..),
_AnyChainBlock'Cardano, BlockRef(), DumpHistoryRequest(),
DumpHistoryResponse(), FetchBlockRequest(), FetchBlockResponse(),
FollowTipRequest(), FollowTipResponse(),
FollowTipResponse'Action(..), _FollowTipResponse'Apply,
_FollowTipResponse'Undo, _FollowTipResponse'Reset
) 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
import qualified Proto.Google.Protobuf.FieldMask
import qualified Proto.Utxorpc.V1alpha.Cardano.Cardano
data AnyChainBlock
= AnyChainBlock'_constructor {AnyChainBlock -> ByteString
_AnyChainBlock'nativeBytes :: !Data.ByteString.ByteString,
AnyChainBlock -> Maybe AnyChainBlock'Chain
_AnyChainBlock'chain :: !(Prelude.Maybe AnyChainBlock'Chain),
AnyChainBlock -> FieldSet
_AnyChainBlock'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (AnyChainBlock -> AnyChainBlock -> Bool
(AnyChainBlock -> AnyChainBlock -> Bool)
-> (AnyChainBlock -> AnyChainBlock -> Bool) -> Eq AnyChainBlock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnyChainBlock -> AnyChainBlock -> Bool
== :: AnyChainBlock -> AnyChainBlock -> Bool
$c/= :: AnyChainBlock -> AnyChainBlock -> Bool
/= :: AnyChainBlock -> AnyChainBlock -> Bool
Prelude.Eq, Eq AnyChainBlock
Eq AnyChainBlock =>
(AnyChainBlock -> AnyChainBlock -> Ordering)
-> (AnyChainBlock -> AnyChainBlock -> Bool)
-> (AnyChainBlock -> AnyChainBlock -> Bool)
-> (AnyChainBlock -> AnyChainBlock -> Bool)
-> (AnyChainBlock -> AnyChainBlock -> Bool)
-> (AnyChainBlock -> AnyChainBlock -> AnyChainBlock)
-> (AnyChainBlock -> AnyChainBlock -> AnyChainBlock)
-> Ord AnyChainBlock
AnyChainBlock -> AnyChainBlock -> Bool
AnyChainBlock -> AnyChainBlock -> Ordering
AnyChainBlock -> AnyChainBlock -> AnyChainBlock
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
$ccompare :: AnyChainBlock -> AnyChainBlock -> Ordering
compare :: AnyChainBlock -> AnyChainBlock -> Ordering
$c< :: AnyChainBlock -> AnyChainBlock -> Bool
< :: AnyChainBlock -> AnyChainBlock -> Bool
$c<= :: AnyChainBlock -> AnyChainBlock -> Bool
<= :: AnyChainBlock -> AnyChainBlock -> Bool
$c> :: AnyChainBlock -> AnyChainBlock -> Bool
> :: AnyChainBlock -> AnyChainBlock -> Bool
$c>= :: AnyChainBlock -> AnyChainBlock -> Bool
>= :: AnyChainBlock -> AnyChainBlock -> Bool
$cmax :: AnyChainBlock -> AnyChainBlock -> AnyChainBlock
max :: AnyChainBlock -> AnyChainBlock -> AnyChainBlock
$cmin :: AnyChainBlock -> AnyChainBlock -> AnyChainBlock
min :: AnyChainBlock -> AnyChainBlock -> AnyChainBlock
Prelude.Ord)
instance Prelude.Show AnyChainBlock where
showsPrec :: Int -> AnyChainBlock -> ShowS
showsPrec Int
_ AnyChainBlock
__x String
__s
= Char -> ShowS
Prelude.showChar
Char
'{'
(String -> ShowS
Prelude.showString
(AnyChainBlock -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort AnyChainBlock
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
data AnyChainBlock'Chain
= AnyChainBlock'Cardano !Proto.Utxorpc.V1alpha.Cardano.Cardano.Block
deriving stock (Int -> AnyChainBlock'Chain -> ShowS
[AnyChainBlock'Chain] -> ShowS
AnyChainBlock'Chain -> String
(Int -> AnyChainBlock'Chain -> ShowS)
-> (AnyChainBlock'Chain -> String)
-> ([AnyChainBlock'Chain] -> ShowS)
-> Show AnyChainBlock'Chain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnyChainBlock'Chain -> ShowS
showsPrec :: Int -> AnyChainBlock'Chain -> ShowS
$cshow :: AnyChainBlock'Chain -> String
show :: AnyChainBlock'Chain -> String
$cshowList :: [AnyChainBlock'Chain] -> ShowS
showList :: [AnyChainBlock'Chain] -> ShowS
Prelude.Show, AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
(AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool)
-> (AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool)
-> Eq AnyChainBlock'Chain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
== :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
$c/= :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
/= :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
Prelude.Eq, Eq AnyChainBlock'Chain
Eq AnyChainBlock'Chain =>
(AnyChainBlock'Chain -> AnyChainBlock'Chain -> Ordering)
-> (AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool)
-> (AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool)
-> (AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool)
-> (AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool)
-> (AnyChainBlock'Chain
-> AnyChainBlock'Chain -> AnyChainBlock'Chain)
-> (AnyChainBlock'Chain
-> AnyChainBlock'Chain -> AnyChainBlock'Chain)
-> Ord AnyChainBlock'Chain
AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
AnyChainBlock'Chain -> AnyChainBlock'Chain -> Ordering
AnyChainBlock'Chain -> AnyChainBlock'Chain -> AnyChainBlock'Chain
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
$ccompare :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Ordering
compare :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Ordering
$c< :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
< :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
$c<= :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
<= :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
$c> :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
> :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
$c>= :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
>= :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> Bool
$cmax :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> AnyChainBlock'Chain
max :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> AnyChainBlock'Chain
$cmin :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> AnyChainBlock'Chain
min :: AnyChainBlock'Chain -> AnyChainBlock'Chain -> AnyChainBlock'Chain
Prelude.Ord)
instance Data.ProtoLens.Field.HasField AnyChainBlock "nativeBytes" Data.ByteString.ByteString where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "nativeBytes"
-> (ByteString -> f ByteString) -> AnyChainBlock -> f AnyChainBlock
fieldOf Proxy# "nativeBytes"
_
= ((ByteString -> f ByteString) -> AnyChainBlock -> f AnyChainBlock)
-> ((ByteString -> f ByteString) -> ByteString -> f ByteString)
-> (ByteString -> f ByteString)
-> AnyChainBlock
-> f AnyChainBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((AnyChainBlock -> ByteString)
-> (AnyChainBlock -> ByteString -> AnyChainBlock)
-> Lens AnyChainBlock AnyChainBlock ByteString ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AnyChainBlock -> ByteString
_AnyChainBlock'nativeBytes
(\ AnyChainBlock
x__ ByteString
y__ -> AnyChainBlock
x__ {_AnyChainBlock'nativeBytes = y__}))
(ByteString -> f ByteString) -> ByteString -> f ByteString
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField AnyChainBlock "maybe'chain" (Prelude.Maybe AnyChainBlock'Chain) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'chain"
-> (Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> AnyChainBlock
-> f AnyChainBlock
fieldOf Proxy# "maybe'chain"
_
= ((Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> AnyChainBlock -> f AnyChainBlock)
-> ((Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> (Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> AnyChainBlock
-> f AnyChainBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((AnyChainBlock -> Maybe AnyChainBlock'Chain)
-> (AnyChainBlock -> Maybe AnyChainBlock'Chain -> AnyChainBlock)
-> Lens
AnyChainBlock
AnyChainBlock
(Maybe AnyChainBlock'Chain)
(Maybe AnyChainBlock'Chain)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AnyChainBlock -> Maybe AnyChainBlock'Chain
_AnyChainBlock'chain
(\ AnyChainBlock
x__ Maybe AnyChainBlock'Chain
y__ -> AnyChainBlock
x__ {_AnyChainBlock'chain = y__}))
(Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField AnyChainBlock "maybe'cardano" (Prelude.Maybe Proto.Utxorpc.V1alpha.Cardano.Cardano.Block) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'cardano"
-> (Maybe Block -> f (Maybe Block))
-> AnyChainBlock
-> f AnyChainBlock
fieldOf Proxy# "maybe'cardano"
_
= ((Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> AnyChainBlock -> f AnyChainBlock)
-> ((Maybe Block -> f (Maybe Block))
-> Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> (Maybe Block -> f (Maybe Block))
-> AnyChainBlock
-> f AnyChainBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((AnyChainBlock -> Maybe AnyChainBlock'Chain)
-> (AnyChainBlock -> Maybe AnyChainBlock'Chain -> AnyChainBlock)
-> Lens
AnyChainBlock
AnyChainBlock
(Maybe AnyChainBlock'Chain)
(Maybe AnyChainBlock'Chain)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AnyChainBlock -> Maybe AnyChainBlock'Chain
_AnyChainBlock'chain
(\ AnyChainBlock
x__ Maybe AnyChainBlock'Chain
y__ -> AnyChainBlock
x__ {_AnyChainBlock'chain = y__}))
((Maybe AnyChainBlock'Chain -> Maybe Block)
-> (Maybe AnyChainBlock'Chain
-> Maybe Block -> Maybe AnyChainBlock'Chain)
-> Lens
(Maybe AnyChainBlock'Chain)
(Maybe AnyChainBlock'Chain)
(Maybe Block)
(Maybe Block)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
(\ Maybe AnyChainBlock'Chain
x__
-> case Maybe AnyChainBlock'Chain
x__ of
(Prelude.Just (AnyChainBlock'Cardano Block
x__val))
-> Block -> Maybe Block
forall a. a -> Maybe a
Prelude.Just Block
x__val
Maybe AnyChainBlock'Chain
_otherwise -> Maybe Block
forall a. Maybe a
Prelude.Nothing)
(\ Maybe AnyChainBlock'Chain
_ Maybe Block
y__ -> (Block -> AnyChainBlock'Chain)
-> Maybe Block -> Maybe AnyChainBlock'Chain
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap Block -> AnyChainBlock'Chain
AnyChainBlock'Cardano Maybe Block
y__))
instance Data.ProtoLens.Field.HasField AnyChainBlock "cardano" Proto.Utxorpc.V1alpha.Cardano.Cardano.Block where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "cardano"
-> (Block -> f Block) -> AnyChainBlock -> f AnyChainBlock
fieldOf Proxy# "cardano"
_
= ((Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> AnyChainBlock -> f AnyChainBlock)
-> ((Block -> f Block)
-> Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> (Block -> f Block)
-> AnyChainBlock
-> f AnyChainBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((AnyChainBlock -> Maybe AnyChainBlock'Chain)
-> (AnyChainBlock -> Maybe AnyChainBlock'Chain -> AnyChainBlock)
-> Lens
AnyChainBlock
AnyChainBlock
(Maybe AnyChainBlock'Chain)
(Maybe AnyChainBlock'Chain)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AnyChainBlock -> Maybe AnyChainBlock'Chain
_AnyChainBlock'chain
(\ AnyChainBlock
x__ Maybe AnyChainBlock'Chain
y__ -> AnyChainBlock
x__ {_AnyChainBlock'chain = y__}))
(((Maybe Block -> f (Maybe Block))
-> Maybe AnyChainBlock'Chain -> f (Maybe AnyChainBlock'Chain))
-> ((Block -> f Block) -> Maybe Block -> f (Maybe Block))
-> (Block -> f Block)
-> Maybe AnyChainBlock'Chain
-> f (Maybe AnyChainBlock'Chain)
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Maybe AnyChainBlock'Chain -> Maybe Block)
-> (Maybe AnyChainBlock'Chain
-> Maybe Block -> Maybe AnyChainBlock'Chain)
-> Lens
(Maybe AnyChainBlock'Chain)
(Maybe AnyChainBlock'Chain)
(Maybe Block)
(Maybe Block)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
(\ Maybe AnyChainBlock'Chain
x__
-> case Maybe AnyChainBlock'Chain
x__ of
(Prelude.Just (AnyChainBlock'Cardano Block
x__val))
-> Block -> Maybe Block
forall a. a -> Maybe a
Prelude.Just Block
x__val
Maybe AnyChainBlock'Chain
_otherwise -> Maybe Block
forall a. Maybe a
Prelude.Nothing)
(\ Maybe AnyChainBlock'Chain
_ Maybe Block
y__ -> (Block -> AnyChainBlock'Chain)
-> Maybe Block -> Maybe AnyChainBlock'Chain
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap Block -> AnyChainBlock'Chain
AnyChainBlock'Cardano Maybe Block
y__))
(Block -> Lens' (Maybe Block) Block
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens Block
forall msg. Message msg => msg
Data.ProtoLens.defMessage))
instance Data.ProtoLens.Message AnyChainBlock where
messageName :: Proxy AnyChainBlock -> Text
messageName Proxy AnyChainBlock
_ = String -> Text
Data.Text.pack String
"utxorpc.v1alpha.sync.AnyChainBlock"
packedMessageDescriptor :: Proxy AnyChainBlock -> ByteString
packedMessageDescriptor Proxy AnyChainBlock
_
= ByteString
"\n\
\\rAnyChainBlock\DC2!\n\
\\fnative_bytes\CAN\SOH \SOH(\fR\vnativeBytes\DC2:\n\
\\acardano\CAN\STX \SOH(\v2\RS.utxorpc.v1alpha.cardano.BlockH\NULR\acardanoB\a\n\
\\ENQchain"
packedFileDescriptor :: Proxy AnyChainBlock -> ByteString
packedFileDescriptor Proxy AnyChainBlock
_ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor AnyChainBlock)
fieldsByTag
= let
nativeBytes__field_descriptor :: FieldDescriptor AnyChainBlock
nativeBytes__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor AnyChainBlock ByteString
-> FieldDescriptor AnyChainBlock
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"native_bytes"
(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 AnyChainBlock AnyChainBlock ByteString ByteString
-> FieldAccessor AnyChainBlock ByteString
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault ByteString
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"nativeBytes")) ::
Data.ProtoLens.FieldDescriptor AnyChainBlock
cardano__field_descriptor :: FieldDescriptor AnyChainBlock
cardano__field_descriptor
= String
-> FieldTypeDescriptor Block
-> FieldAccessor AnyChainBlock Block
-> FieldDescriptor AnyChainBlock
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"cardano"
(MessageOrGroup -> FieldTypeDescriptor Block
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Proto.Utxorpc.V1alpha.Cardano.Cardano.Block)
(Lens' AnyChainBlock (Maybe Block)
-> FieldAccessor AnyChainBlock Block
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'cardano")) ::
Data.ProtoLens.FieldDescriptor AnyChainBlock
in
[(Tag, FieldDescriptor AnyChainBlock)]
-> Map Tag (FieldDescriptor AnyChainBlock)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor AnyChainBlock
nativeBytes__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor AnyChainBlock
cardano__field_descriptor)]
unknownFields :: Lens' AnyChainBlock FieldSet
unknownFields
= (AnyChainBlock -> FieldSet)
-> (AnyChainBlock -> FieldSet -> AnyChainBlock)
-> Lens' AnyChainBlock FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
AnyChainBlock -> FieldSet
_AnyChainBlock'_unknownFields
(\ AnyChainBlock
x__ FieldSet
y__ -> AnyChainBlock
x__ {_AnyChainBlock'_unknownFields = y__})
defMessage :: AnyChainBlock
defMessage
= AnyChainBlock'_constructor
{_AnyChainBlock'nativeBytes :: ByteString
_AnyChainBlock'nativeBytes = ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_AnyChainBlock'chain :: Maybe AnyChainBlock'Chain
_AnyChainBlock'chain = Maybe AnyChainBlock'Chain
forall a. Maybe a
Prelude.Nothing,
_AnyChainBlock'_unknownFields :: FieldSet
_AnyChainBlock'_unknownFields = []}
parseMessage :: Parser AnyChainBlock
parseMessage
= let
loop ::
AnyChainBlock -> Data.ProtoLens.Encoding.Bytes.Parser AnyChainBlock
loop :: AnyChainBlock -> Parser AnyChainBlock
loop AnyChainBlock
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 a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
String
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
AnyChainBlock -> Parser AnyChainBlock
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter AnyChainBlock AnyChainBlock FieldSet FieldSet
-> (FieldSet -> FieldSet) -> AnyChainBlock -> AnyChainBlock
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f AnyChainBlock FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' AnyChainBlock FieldSet
Setter AnyChainBlock AnyChainBlock FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) AnyChainBlock
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
Word64
10
-> 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))
String
"native_bytes"
AnyChainBlock -> Parser AnyChainBlock
loop
(Setter AnyChainBlock AnyChainBlock ByteString ByteString
-> ByteString -> AnyChainBlock -> AnyChainBlock
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"nativeBytes") ByteString
y AnyChainBlock
x)
Word64
18
-> do Block
y <- Parser Block -> String -> Parser Block
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser Block -> Parser Block
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 Block
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"cardano"
AnyChainBlock -> Parser AnyChainBlock
loop (Setter AnyChainBlock AnyChainBlock Block Block
-> Block -> AnyChainBlock -> AnyChainBlock
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"cardano") Block
y AnyChainBlock
x)
Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
AnyChainBlock -> Parser AnyChainBlock
loop
(Setter AnyChainBlock AnyChainBlock FieldSet FieldSet
-> (FieldSet -> FieldSet) -> AnyChainBlock -> AnyChainBlock
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f AnyChainBlock FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' AnyChainBlock FieldSet
Setter AnyChainBlock AnyChainBlock FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) AnyChainBlock
x)
in
Parser AnyChainBlock -> String -> Parser AnyChainBlock
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do AnyChainBlock -> Parser AnyChainBlock
loop AnyChainBlock
forall msg. Message msg => msg
Data.ProtoLens.defMessage) String
"AnyChainBlock"
buildMessage :: AnyChainBlock -> Builder
buildMessage
= \ AnyChainBlock
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(let
_v :: ByteString
_v
= FoldLike
ByteString AnyChainBlock AnyChainBlock ByteString ByteString
-> AnyChainBlock -> ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"nativeBytes") AnyChainBlock
_x
in
if ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) ByteString
_v ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
Builder
forall a. Monoid a => a
Data.Monoid.mempty
else
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
((\ 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 AnyChainBlock'Chain)
AnyChainBlock
AnyChainBlock
(Maybe AnyChainBlock'Chain)
(Maybe AnyChainBlock'Chain)
-> AnyChainBlock -> Maybe AnyChainBlock'Chain
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'chain") AnyChainBlock
_x
of
Maybe AnyChainBlock'Chain
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just (AnyChainBlock'Cardano Block
v))
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
((ByteString -> Builder)
-> (Block -> ByteString) -> Block -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
Block -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage Block
v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike FieldSet AnyChainBlock AnyChainBlock FieldSet FieldSet
-> AnyChainBlock -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet AnyChainBlock AnyChainBlock FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' AnyChainBlock FieldSet
Data.ProtoLens.unknownFields AnyChainBlock
_x)))
instance Control.DeepSeq.NFData AnyChainBlock where
rnf :: AnyChainBlock -> ()
rnf
= \ AnyChainBlock
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(AnyChainBlock -> FieldSet
_AnyChainBlock'_unknownFields AnyChainBlock
x__)
(ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(AnyChainBlock -> ByteString
_AnyChainBlock'nativeBytes AnyChainBlock
x__)
(Maybe AnyChainBlock'Chain -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (AnyChainBlock -> Maybe AnyChainBlock'Chain
_AnyChainBlock'chain AnyChainBlock
x__) ()))
instance Control.DeepSeq.NFData AnyChainBlock'Chain where
rnf :: AnyChainBlock'Chain -> ()
rnf (AnyChainBlock'Cardano Block
x__) = Block -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf Block
x__
_AnyChainBlock'Cardano ::
Data.ProtoLens.Prism.Prism' AnyChainBlock'Chain Proto.Utxorpc.V1alpha.Cardano.Cardano.Block
_AnyChainBlock'Cardano :: Prism' AnyChainBlock'Chain Block
_AnyChainBlock'Cardano
= (Block -> AnyChainBlock'Chain)
-> (AnyChainBlock'Chain -> Maybe Block)
-> Prism' AnyChainBlock'Chain Block
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
Data.ProtoLens.Prism.prism'
Block -> AnyChainBlock'Chain
AnyChainBlock'Cardano
(\ AnyChainBlock'Chain
p__
-> case AnyChainBlock'Chain
p__ of
(AnyChainBlock'Cardano Block
p__val) -> Block -> Maybe Block
forall a. a -> Maybe a
Prelude.Just Block
p__val)
data BlockRef
= BlockRef'_constructor {BlockRef -> Word64
_BlockRef'index :: !Data.Word.Word64,
BlockRef -> ByteString
_BlockRef'hash :: !Data.ByteString.ByteString,
BlockRef -> FieldSet
_BlockRef'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (BlockRef -> BlockRef -> Bool
(BlockRef -> BlockRef -> Bool)
-> (BlockRef -> BlockRef -> Bool) -> Eq BlockRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BlockRef -> BlockRef -> Bool
== :: BlockRef -> BlockRef -> Bool
$c/= :: BlockRef -> BlockRef -> Bool
/= :: BlockRef -> BlockRef -> Bool
Prelude.Eq, Eq BlockRef
Eq BlockRef =>
(BlockRef -> BlockRef -> Ordering)
-> (BlockRef -> BlockRef -> Bool)
-> (BlockRef -> BlockRef -> Bool)
-> (BlockRef -> BlockRef -> Bool)
-> (BlockRef -> BlockRef -> Bool)
-> (BlockRef -> BlockRef -> BlockRef)
-> (BlockRef -> BlockRef -> BlockRef)
-> Ord BlockRef
BlockRef -> BlockRef -> Bool
BlockRef -> BlockRef -> Ordering
BlockRef -> BlockRef -> BlockRef
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
$ccompare :: BlockRef -> BlockRef -> Ordering
compare :: BlockRef -> BlockRef -> Ordering
$c< :: BlockRef -> BlockRef -> Bool
< :: BlockRef -> BlockRef -> Bool
$c<= :: BlockRef -> BlockRef -> Bool
<= :: BlockRef -> BlockRef -> Bool
$c> :: BlockRef -> BlockRef -> Bool
> :: BlockRef -> BlockRef -> Bool
$c>= :: BlockRef -> BlockRef -> Bool
>= :: BlockRef -> BlockRef -> Bool
$cmax :: BlockRef -> BlockRef -> BlockRef
max :: BlockRef -> BlockRef -> BlockRef
$cmin :: BlockRef -> BlockRef -> BlockRef
min :: BlockRef -> BlockRef -> BlockRef
Prelude.Ord)
instance Prelude.Show BlockRef where
showsPrec :: Int -> BlockRef -> ShowS
showsPrec Int
_ BlockRef
__x String
__s
= Char -> ShowS
Prelude.showChar
Char
'{'
(String -> ShowS
Prelude.showString
(BlockRef -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort BlockRef
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField BlockRef "index" Data.Word.Word64 where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "index" -> (Word64 -> f Word64) -> BlockRef -> f BlockRef
fieldOf Proxy# "index"
_
= ((Word64 -> f Word64) -> BlockRef -> f BlockRef)
-> ((Word64 -> f Word64) -> Word64 -> f Word64)
-> (Word64 -> f Word64)
-> BlockRef
-> f BlockRef
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BlockRef -> Word64)
-> (BlockRef -> Word64 -> BlockRef)
-> Lens BlockRef BlockRef Word64 Word64
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BlockRef -> Word64
_BlockRef'index (\ BlockRef
x__ Word64
y__ -> BlockRef
x__ {_BlockRef'index = y__}))
(Word64 -> f Word64) -> Word64 -> f Word64
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField BlockRef "hash" Data.ByteString.ByteString where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "hash"
-> (ByteString -> f ByteString) -> BlockRef -> f BlockRef
fieldOf Proxy# "hash"
_
= ((ByteString -> f ByteString) -> BlockRef -> f BlockRef)
-> ((ByteString -> f ByteString) -> ByteString -> f ByteString)
-> (ByteString -> f ByteString)
-> BlockRef
-> f BlockRef
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((BlockRef -> ByteString)
-> (BlockRef -> ByteString -> BlockRef)
-> Lens BlockRef BlockRef ByteString ByteString
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BlockRef -> ByteString
_BlockRef'hash (\ BlockRef
x__ ByteString
y__ -> BlockRef
x__ {_BlockRef'hash = y__}))
(ByteString -> f ByteString) -> ByteString -> f ByteString
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message BlockRef where
messageName :: Proxy BlockRef -> Text
messageName Proxy BlockRef
_ = String -> Text
Data.Text.pack String
"utxorpc.v1alpha.sync.BlockRef"
packedMessageDescriptor :: Proxy BlockRef -> ByteString
packedMessageDescriptor Proxy BlockRef
_
= ByteString
"\n\
\\bBlockRef\DC2\DC4\n\
\\ENQindex\CAN\SOH \SOH(\EOTR\ENQindex\DC2\DC2\n\
\\EOThash\CAN\STX \SOH(\fR\EOThash"
packedFileDescriptor :: Proxy BlockRef -> ByteString
packedFileDescriptor Proxy BlockRef
_ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor BlockRef)
fieldsByTag
= let
index__field_descriptor :: FieldDescriptor BlockRef
index__field_descriptor
= String
-> FieldTypeDescriptor Word64
-> FieldAccessor BlockRef Word64
-> FieldDescriptor BlockRef
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"index"
(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 BlockRef BlockRef Word64 Word64
-> FieldAccessor BlockRef Word64
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word64
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"index")) ::
Data.ProtoLens.FieldDescriptor BlockRef
hash__field_descriptor :: FieldDescriptor BlockRef
hash__field_descriptor
= String
-> FieldTypeDescriptor ByteString
-> FieldAccessor BlockRef ByteString
-> FieldDescriptor BlockRef
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"hash"
(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 BlockRef BlockRef ByteString ByteString
-> FieldAccessor BlockRef ByteString
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault ByteString
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"hash")) ::
Data.ProtoLens.FieldDescriptor BlockRef
in
[(Tag, FieldDescriptor BlockRef)]
-> Map Tag (FieldDescriptor BlockRef)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor BlockRef
index__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor BlockRef
hash__field_descriptor)]
unknownFields :: Lens' BlockRef FieldSet
unknownFields
= (BlockRef -> FieldSet)
-> (BlockRef -> FieldSet -> BlockRef) -> Lens' BlockRef FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
BlockRef -> FieldSet
_BlockRef'_unknownFields
(\ BlockRef
x__ FieldSet
y__ -> BlockRef
x__ {_BlockRef'_unknownFields = y__})
defMessage :: BlockRef
defMessage
= BlockRef'_constructor
{_BlockRef'index :: Word64
_BlockRef'index = Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_BlockRef'hash :: ByteString
_BlockRef'hash = ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_BlockRef'_unknownFields :: FieldSet
_BlockRef'_unknownFields = []}
parseMessage :: Parser BlockRef
parseMessage
= let
loop :: BlockRef -> Data.ProtoLens.Encoding.Bytes.Parser BlockRef
loop :: BlockRef -> Parser BlockRef
loop BlockRef
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 a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
String
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
BlockRef -> Parser BlockRef
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter BlockRef BlockRef FieldSet FieldSet
-> (FieldSet -> FieldSet) -> BlockRef -> BlockRef
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f BlockRef FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' BlockRef FieldSet
Setter BlockRef BlockRef FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) BlockRef
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
Word64
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 String
"index"
BlockRef -> Parser BlockRef
loop (Setter BlockRef BlockRef Word64 Word64
-> Word64 -> BlockRef -> BlockRef
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"index") Word64
y BlockRef
x)
Word64
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))
String
"hash"
BlockRef -> Parser BlockRef
loop (Setter BlockRef BlockRef ByteString ByteString
-> ByteString -> BlockRef -> BlockRef
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"hash") ByteString
y BlockRef
x)
Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
BlockRef -> Parser BlockRef
loop
(Setter BlockRef BlockRef FieldSet FieldSet
-> (FieldSet -> FieldSet) -> BlockRef -> BlockRef
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f BlockRef FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' BlockRef FieldSet
Setter BlockRef BlockRef FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) BlockRef
x)
in
Parser BlockRef -> String -> Parser BlockRef
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do BlockRef -> Parser BlockRef
loop BlockRef
forall msg. Message msg => msg
Data.ProtoLens.defMessage) String
"BlockRef"
buildMessage :: BlockRef -> Builder
buildMessage
= \ BlockRef
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(let
_v :: Word64
_v = FoldLike Word64 BlockRef BlockRef Word64 Word64
-> BlockRef -> Word64
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"index") BlockRef
_x
in
if Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Word64
_v Word64
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
Builder
forall a. Monoid a => a
Data.Monoid.mempty
else
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
8)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(let _v :: ByteString
_v = FoldLike ByteString BlockRef BlockRef ByteString ByteString
-> BlockRef -> ByteString
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"hash") BlockRef
_x
in
if ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) ByteString
_v ByteString
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
Builder
forall a. Monoid a => a
Data.Monoid.mempty
else
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
((\ 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 BlockRef BlockRef FieldSet FieldSet
-> BlockRef -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike FieldSet BlockRef BlockRef FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' BlockRef FieldSet
Data.ProtoLens.unknownFields BlockRef
_x)))
instance Control.DeepSeq.NFData BlockRef where
rnf :: BlockRef -> ()
rnf
= \ BlockRef
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BlockRef -> FieldSet
_BlockRef'_unknownFields BlockRef
x__)
(Word64 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(BlockRef -> Word64
_BlockRef'index BlockRef
x__)
(ByteString -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (BlockRef -> ByteString
_BlockRef'hash BlockRef
x__) ()))
data DumpHistoryRequest
= DumpHistoryRequest'_constructor {DumpHistoryRequest -> Maybe BlockRef
_DumpHistoryRequest'startToken :: !(Prelude.Maybe BlockRef),
DumpHistoryRequest -> Word32
_DumpHistoryRequest'maxItems :: !Data.Word.Word32,
DumpHistoryRequest -> Maybe FieldMask
_DumpHistoryRequest'fieldMask :: !(Prelude.Maybe Proto.Google.Protobuf.FieldMask.FieldMask),
DumpHistoryRequest -> FieldSet
_DumpHistoryRequest'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (DumpHistoryRequest -> DumpHistoryRequest -> Bool
(DumpHistoryRequest -> DumpHistoryRequest -> Bool)
-> (DumpHistoryRequest -> DumpHistoryRequest -> Bool)
-> Eq DumpHistoryRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
== :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
$c/= :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
/= :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
Prelude.Eq, Eq DumpHistoryRequest
Eq DumpHistoryRequest =>
(DumpHistoryRequest -> DumpHistoryRequest -> Ordering)
-> (DumpHistoryRequest -> DumpHistoryRequest -> Bool)
-> (DumpHistoryRequest -> DumpHistoryRequest -> Bool)
-> (DumpHistoryRequest -> DumpHistoryRequest -> Bool)
-> (DumpHistoryRequest -> DumpHistoryRequest -> Bool)
-> (DumpHistoryRequest -> DumpHistoryRequest -> DumpHistoryRequest)
-> (DumpHistoryRequest -> DumpHistoryRequest -> DumpHistoryRequest)
-> Ord DumpHistoryRequest
DumpHistoryRequest -> DumpHistoryRequest -> Bool
DumpHistoryRequest -> DumpHistoryRequest -> Ordering
DumpHistoryRequest -> DumpHistoryRequest -> DumpHistoryRequest
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
$ccompare :: DumpHistoryRequest -> DumpHistoryRequest -> Ordering
compare :: DumpHistoryRequest -> DumpHistoryRequest -> Ordering
$c< :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
< :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
$c<= :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
<= :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
$c> :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
> :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
$c>= :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
>= :: DumpHistoryRequest -> DumpHistoryRequest -> Bool
$cmax :: DumpHistoryRequest -> DumpHistoryRequest -> DumpHistoryRequest
max :: DumpHistoryRequest -> DumpHistoryRequest -> DumpHistoryRequest
$cmin :: DumpHistoryRequest -> DumpHistoryRequest -> DumpHistoryRequest
min :: DumpHistoryRequest -> DumpHistoryRequest -> DumpHistoryRequest
Prelude.Ord)
instance Prelude.Show DumpHistoryRequest where
showsPrec :: Int -> DumpHistoryRequest -> ShowS
showsPrec Int
_ DumpHistoryRequest
__x String
__s
= Char -> ShowS
Prelude.showChar
Char
'{'
(String -> ShowS
Prelude.showString
(DumpHistoryRequest -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort DumpHistoryRequest
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField DumpHistoryRequest "startToken" BlockRef where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "startToken"
-> (BlockRef -> f BlockRef)
-> DumpHistoryRequest
-> f DumpHistoryRequest
fieldOf Proxy# "startToken"
_
= ((Maybe BlockRef -> f (Maybe BlockRef))
-> DumpHistoryRequest -> f DumpHistoryRequest)
-> ((BlockRef -> f BlockRef)
-> Maybe BlockRef -> f (Maybe BlockRef))
-> (BlockRef -> f BlockRef)
-> DumpHistoryRequest
-> f DumpHistoryRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((DumpHistoryRequest -> Maybe BlockRef)
-> (DumpHistoryRequest -> Maybe BlockRef -> DumpHistoryRequest)
-> Lens
DumpHistoryRequest
DumpHistoryRequest
(Maybe BlockRef)
(Maybe BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryRequest -> Maybe BlockRef
_DumpHistoryRequest'startToken
(\ DumpHistoryRequest
x__ Maybe BlockRef
y__ -> DumpHistoryRequest
x__ {_DumpHistoryRequest'startToken = y__}))
(BlockRef -> Lens' (Maybe BlockRef) BlockRef
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens BlockRef
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField DumpHistoryRequest "maybe'startToken" (Prelude.Maybe BlockRef) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'startToken"
-> (Maybe BlockRef -> f (Maybe BlockRef))
-> DumpHistoryRequest
-> f DumpHistoryRequest
fieldOf Proxy# "maybe'startToken"
_
= ((Maybe BlockRef -> f (Maybe BlockRef))
-> DumpHistoryRequest -> f DumpHistoryRequest)
-> ((Maybe BlockRef -> f (Maybe BlockRef))
-> Maybe BlockRef -> f (Maybe BlockRef))
-> (Maybe BlockRef -> f (Maybe BlockRef))
-> DumpHistoryRequest
-> f DumpHistoryRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((DumpHistoryRequest -> Maybe BlockRef)
-> (DumpHistoryRequest -> Maybe BlockRef -> DumpHistoryRequest)
-> Lens
DumpHistoryRequest
DumpHistoryRequest
(Maybe BlockRef)
(Maybe BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryRequest -> Maybe BlockRef
_DumpHistoryRequest'startToken
(\ DumpHistoryRequest
x__ Maybe BlockRef
y__ -> DumpHistoryRequest
x__ {_DumpHistoryRequest'startToken = y__}))
(Maybe BlockRef -> f (Maybe BlockRef))
-> Maybe BlockRef -> f (Maybe BlockRef)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField DumpHistoryRequest "maxItems" Data.Word.Word32 where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maxItems"
-> (Word32 -> f Word32)
-> DumpHistoryRequest
-> f DumpHistoryRequest
fieldOf Proxy# "maxItems"
_
= ((Word32 -> f Word32)
-> DumpHistoryRequest -> f DumpHistoryRequest)
-> ((Word32 -> f Word32) -> Word32 -> f Word32)
-> (Word32 -> f Word32)
-> DumpHistoryRequest
-> f DumpHistoryRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((DumpHistoryRequest -> Word32)
-> (DumpHistoryRequest -> Word32 -> DumpHistoryRequest)
-> Lens DumpHistoryRequest DumpHistoryRequest Word32 Word32
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryRequest -> Word32
_DumpHistoryRequest'maxItems
(\ DumpHistoryRequest
x__ Word32
y__ -> DumpHistoryRequest
x__ {_DumpHistoryRequest'maxItems = y__}))
(Word32 -> f Word32) -> Word32 -> f Word32
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField DumpHistoryRequest "fieldMask" Proto.Google.Protobuf.FieldMask.FieldMask where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "fieldMask"
-> (FieldMask -> f FieldMask)
-> DumpHistoryRequest
-> f DumpHistoryRequest
fieldOf Proxy# "fieldMask"
_
= ((Maybe FieldMask -> f (Maybe FieldMask))
-> DumpHistoryRequest -> f DumpHistoryRequest)
-> ((FieldMask -> f FieldMask)
-> Maybe FieldMask -> f (Maybe FieldMask))
-> (FieldMask -> f FieldMask)
-> DumpHistoryRequest
-> f DumpHistoryRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((DumpHistoryRequest -> Maybe FieldMask)
-> (DumpHistoryRequest -> Maybe FieldMask -> DumpHistoryRequest)
-> Lens
DumpHistoryRequest
DumpHistoryRequest
(Maybe FieldMask)
(Maybe FieldMask)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryRequest -> Maybe FieldMask
_DumpHistoryRequest'fieldMask
(\ DumpHistoryRequest
x__ Maybe FieldMask
y__ -> DumpHistoryRequest
x__ {_DumpHistoryRequest'fieldMask = y__}))
(FieldMask -> Lens' (Maybe FieldMask) FieldMask
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens FieldMask
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField DumpHistoryRequest "maybe'fieldMask" (Prelude.Maybe Proto.Google.Protobuf.FieldMask.FieldMask) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'fieldMask"
-> (Maybe FieldMask -> f (Maybe FieldMask))
-> DumpHistoryRequest
-> f DumpHistoryRequest
fieldOf Proxy# "maybe'fieldMask"
_
= ((Maybe FieldMask -> f (Maybe FieldMask))
-> DumpHistoryRequest -> f DumpHistoryRequest)
-> ((Maybe FieldMask -> f (Maybe FieldMask))
-> Maybe FieldMask -> f (Maybe FieldMask))
-> (Maybe FieldMask -> f (Maybe FieldMask))
-> DumpHistoryRequest
-> f DumpHistoryRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((DumpHistoryRequest -> Maybe FieldMask)
-> (DumpHistoryRequest -> Maybe FieldMask -> DumpHistoryRequest)
-> Lens
DumpHistoryRequest
DumpHistoryRequest
(Maybe FieldMask)
(Maybe FieldMask)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryRequest -> Maybe FieldMask
_DumpHistoryRequest'fieldMask
(\ DumpHistoryRequest
x__ Maybe FieldMask
y__ -> DumpHistoryRequest
x__ {_DumpHistoryRequest'fieldMask = y__}))
(Maybe FieldMask -> f (Maybe FieldMask))
-> Maybe FieldMask -> f (Maybe FieldMask)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message DumpHistoryRequest where
messageName :: Proxy DumpHistoryRequest -> Text
messageName Proxy DumpHistoryRequest
_
= String -> Text
Data.Text.pack String
"utxorpc.v1alpha.sync.DumpHistoryRequest"
packedMessageDescriptor :: Proxy DumpHistoryRequest -> ByteString
packedMessageDescriptor Proxy DumpHistoryRequest
_
= ByteString
"\n\
\\DC2DumpHistoryRequest\DC2?\n\
\\vstart_token\CAN\STX \SOH(\v2\RS.utxorpc.v1alpha.sync.BlockRefR\n\
\startToken\DC2\ESC\n\
\\tmax_items\CAN\ETX \SOH(\rR\bmaxItems\DC29\n\
\\n\
\field_mask\CAN\EOT \SOH(\v2\SUB.google.protobuf.FieldMaskR\tfieldMask"
packedFileDescriptor :: Proxy DumpHistoryRequest -> ByteString
packedFileDescriptor Proxy DumpHistoryRequest
_ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor DumpHistoryRequest)
fieldsByTag
= let
startToken__field_descriptor :: FieldDescriptor DumpHistoryRequest
startToken__field_descriptor
= String
-> FieldTypeDescriptor BlockRef
-> FieldAccessor DumpHistoryRequest BlockRef
-> FieldDescriptor DumpHistoryRequest
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"start_token"
(MessageOrGroup -> FieldTypeDescriptor BlockRef
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor BlockRef)
(Lens
DumpHistoryRequest
DumpHistoryRequest
(Maybe BlockRef)
(Maybe BlockRef)
-> FieldAccessor DumpHistoryRequest BlockRef
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'startToken")) ::
Data.ProtoLens.FieldDescriptor DumpHistoryRequest
maxItems__field_descriptor :: FieldDescriptor DumpHistoryRequest
maxItems__field_descriptor
= String
-> FieldTypeDescriptor Word32
-> FieldAccessor DumpHistoryRequest Word32
-> FieldDescriptor DumpHistoryRequest
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"max_items"
(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 DumpHistoryRequest DumpHistoryRequest Word32 Word32
-> FieldAccessor DumpHistoryRequest Word32
forall value msg.
WireDefault value -> Lens' msg value -> FieldAccessor msg value
Data.ProtoLens.PlainField
WireDefault Word32
forall value. (FieldDefault value, Eq value) => WireDefault value
Data.ProtoLens.Optional
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maxItems")) ::
Data.ProtoLens.FieldDescriptor DumpHistoryRequest
fieldMask__field_descriptor :: FieldDescriptor DumpHistoryRequest
fieldMask__field_descriptor
= String
-> FieldTypeDescriptor FieldMask
-> FieldAccessor DumpHistoryRequest FieldMask
-> FieldDescriptor DumpHistoryRequest
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"field_mask"
(MessageOrGroup -> FieldTypeDescriptor FieldMask
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Proto.Google.Protobuf.FieldMask.FieldMask)
(Lens
DumpHistoryRequest
DumpHistoryRequest
(Maybe FieldMask)
(Maybe FieldMask)
-> FieldAccessor DumpHistoryRequest FieldMask
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'fieldMask")) ::
Data.ProtoLens.FieldDescriptor DumpHistoryRequest
in
[(Tag, FieldDescriptor DumpHistoryRequest)]
-> Map Tag (FieldDescriptor DumpHistoryRequest)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor DumpHistoryRequest
startToken__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag Int
3, FieldDescriptor DumpHistoryRequest
maxItems__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag Int
4, FieldDescriptor DumpHistoryRequest
fieldMask__field_descriptor)]
unknownFields :: Lens' DumpHistoryRequest FieldSet
unknownFields
= (DumpHistoryRequest -> FieldSet)
-> (DumpHistoryRequest -> FieldSet -> DumpHistoryRequest)
-> Lens' DumpHistoryRequest FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryRequest -> FieldSet
_DumpHistoryRequest'_unknownFields
(\ DumpHistoryRequest
x__ FieldSet
y__ -> DumpHistoryRequest
x__ {_DumpHistoryRequest'_unknownFields = y__})
defMessage :: DumpHistoryRequest
defMessage
= DumpHistoryRequest'_constructor
{_DumpHistoryRequest'startToken :: Maybe BlockRef
_DumpHistoryRequest'startToken = Maybe BlockRef
forall a. Maybe a
Prelude.Nothing,
_DumpHistoryRequest'maxItems :: Word32
_DumpHistoryRequest'maxItems = Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault,
_DumpHistoryRequest'fieldMask :: Maybe FieldMask
_DumpHistoryRequest'fieldMask = Maybe FieldMask
forall a. Maybe a
Prelude.Nothing,
_DumpHistoryRequest'_unknownFields :: FieldSet
_DumpHistoryRequest'_unknownFields = []}
parseMessage :: Parser DumpHistoryRequest
parseMessage
= let
loop ::
DumpHistoryRequest
-> Data.ProtoLens.Encoding.Bytes.Parser DumpHistoryRequest
loop :: DumpHistoryRequest -> Parser DumpHistoryRequest
loop DumpHistoryRequest
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 a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
String
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
DumpHistoryRequest -> Parser DumpHistoryRequest
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter DumpHistoryRequest DumpHistoryRequest FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> DumpHistoryRequest
-> DumpHistoryRequest
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f DumpHistoryRequest FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' DumpHistoryRequest FieldSet
Setter DumpHistoryRequest DumpHistoryRequest FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) DumpHistoryRequest
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
Word64
18
-> do BlockRef
y <- Parser BlockRef -> String -> Parser BlockRef
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser BlockRef -> Parser BlockRef
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 BlockRef
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"start_token"
DumpHistoryRequest -> Parser DumpHistoryRequest
loop
(Setter DumpHistoryRequest DumpHistoryRequest BlockRef BlockRef
-> BlockRef -> DumpHistoryRequest -> DumpHistoryRequest
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"startToken") BlockRef
y DumpHistoryRequest
x)
Word64
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 a b. (a -> b) -> Parser a -> Parser b
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)
String
"max_items"
DumpHistoryRequest -> Parser DumpHistoryRequest
loop
(Setter DumpHistoryRequest DumpHistoryRequest Word32 Word32
-> Word32 -> DumpHistoryRequest -> DumpHistoryRequest
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maxItems") Word32
y DumpHistoryRequest
x)
Word64
34
-> do FieldMask
y <- Parser FieldMask -> String -> Parser FieldMask
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser FieldMask -> Parser FieldMask
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 FieldMask
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"field_mask"
DumpHistoryRequest -> Parser DumpHistoryRequest
loop
(Setter DumpHistoryRequest DumpHistoryRequest FieldMask FieldMask
-> FieldMask -> DumpHistoryRequest -> DumpHistoryRequest
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"fieldMask") FieldMask
y DumpHistoryRequest
x)
Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
DumpHistoryRequest -> Parser DumpHistoryRequest
loop
(Setter DumpHistoryRequest DumpHistoryRequest FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> DumpHistoryRequest
-> DumpHistoryRequest
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f DumpHistoryRequest FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' DumpHistoryRequest FieldSet
Setter DumpHistoryRequest DumpHistoryRequest FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) DumpHistoryRequest
x)
in
Parser DumpHistoryRequest -> String -> Parser DumpHistoryRequest
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do DumpHistoryRequest -> Parser DumpHistoryRequest
loop DumpHistoryRequest
forall msg. Message msg => msg
Data.ProtoLens.defMessage) String
"DumpHistoryRequest"
buildMessage :: DumpHistoryRequest -> Builder
buildMessage
= \ DumpHistoryRequest
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe BlockRef)
DumpHistoryRequest
DumpHistoryRequest
(Maybe BlockRef)
(Maybe BlockRef)
-> DumpHistoryRequest -> Maybe BlockRef
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'startToken") DumpHistoryRequest
_x
of
Maybe BlockRef
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just BlockRef
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
((ByteString -> Builder)
-> (BlockRef -> ByteString) -> BlockRef -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
BlockRef -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage BlockRef
_v))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(let
_v :: Word32
_v = FoldLike Word32 DumpHistoryRequest DumpHistoryRequest Word32 Word32
-> DumpHistoryRequest -> Word32
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maxItems") DumpHistoryRequest
_x
in
if Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
(Prelude.==) Word32
_v Word32
forall value. FieldDefault value => value
Data.ProtoLens.fieldDefault then
Builder
forall a. Monoid a => a
Data.Monoid.mempty
else
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
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.<>)
(case
FoldLike
(Maybe FieldMask)
DumpHistoryRequest
DumpHistoryRequest
(Maybe FieldMask)
(Maybe FieldMask)
-> DumpHistoryRequest -> Maybe FieldMask
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'fieldMask") DumpHistoryRequest
_x
of
Maybe FieldMask
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just FieldMask
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
34)
((ByteString -> Builder)
-> (FieldMask -> ByteString) -> FieldMask -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
FieldMask -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage FieldMask
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet DumpHistoryRequest DumpHistoryRequest FieldSet FieldSet
-> DumpHistoryRequest -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet DumpHistoryRequest DumpHistoryRequest FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' DumpHistoryRequest FieldSet
Data.ProtoLens.unknownFields DumpHistoryRequest
_x))))
instance Control.DeepSeq.NFData DumpHistoryRequest where
rnf :: DumpHistoryRequest -> ()
rnf
= \ DumpHistoryRequest
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(DumpHistoryRequest -> FieldSet
_DumpHistoryRequest'_unknownFields DumpHistoryRequest
x__)
(Maybe BlockRef -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(DumpHistoryRequest -> Maybe BlockRef
_DumpHistoryRequest'startToken DumpHistoryRequest
x__)
(Word32 -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(DumpHistoryRequest -> Word32
_DumpHistoryRequest'maxItems DumpHistoryRequest
x__)
(Maybe FieldMask -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (DumpHistoryRequest -> Maybe FieldMask
_DumpHistoryRequest'fieldMask DumpHistoryRequest
x__) ())))
data DumpHistoryResponse
= DumpHistoryResponse'_constructor {DumpHistoryResponse -> Vector AnyChainBlock
_DumpHistoryResponse'block :: !(Data.Vector.Vector AnyChainBlock),
DumpHistoryResponse -> Maybe BlockRef
_DumpHistoryResponse'nextToken :: !(Prelude.Maybe BlockRef),
DumpHistoryResponse -> FieldSet
_DumpHistoryResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (DumpHistoryResponse -> DumpHistoryResponse -> Bool
(DumpHistoryResponse -> DumpHistoryResponse -> Bool)
-> (DumpHistoryResponse -> DumpHistoryResponse -> Bool)
-> Eq DumpHistoryResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
== :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
$c/= :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
/= :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
Prelude.Eq, Eq DumpHistoryResponse
Eq DumpHistoryResponse =>
(DumpHistoryResponse -> DumpHistoryResponse -> Ordering)
-> (DumpHistoryResponse -> DumpHistoryResponse -> Bool)
-> (DumpHistoryResponse -> DumpHistoryResponse -> Bool)
-> (DumpHistoryResponse -> DumpHistoryResponse -> Bool)
-> (DumpHistoryResponse -> DumpHistoryResponse -> Bool)
-> (DumpHistoryResponse
-> DumpHistoryResponse -> DumpHistoryResponse)
-> (DumpHistoryResponse
-> DumpHistoryResponse -> DumpHistoryResponse)
-> Ord DumpHistoryResponse
DumpHistoryResponse -> DumpHistoryResponse -> Bool
DumpHistoryResponse -> DumpHistoryResponse -> Ordering
DumpHistoryResponse -> DumpHistoryResponse -> DumpHistoryResponse
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
$ccompare :: DumpHistoryResponse -> DumpHistoryResponse -> Ordering
compare :: DumpHistoryResponse -> DumpHistoryResponse -> Ordering
$c< :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
< :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
$c<= :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
<= :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
$c> :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
> :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
$c>= :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
>= :: DumpHistoryResponse -> DumpHistoryResponse -> Bool
$cmax :: DumpHistoryResponse -> DumpHistoryResponse -> DumpHistoryResponse
max :: DumpHistoryResponse -> DumpHistoryResponse -> DumpHistoryResponse
$cmin :: DumpHistoryResponse -> DumpHistoryResponse -> DumpHistoryResponse
min :: DumpHistoryResponse -> DumpHistoryResponse -> DumpHistoryResponse
Prelude.Ord)
instance Prelude.Show DumpHistoryResponse where
showsPrec :: Int -> DumpHistoryResponse -> ShowS
showsPrec Int
_ DumpHistoryResponse
__x String
__s
= Char -> ShowS
Prelude.showChar
Char
'{'
(String -> ShowS
Prelude.showString
(DumpHistoryResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort DumpHistoryResponse
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField DumpHistoryResponse "block" [AnyChainBlock] where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "block"
-> ([AnyChainBlock] -> f [AnyChainBlock])
-> DumpHistoryResponse
-> f DumpHistoryResponse
fieldOf Proxy# "block"
_
= ((Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> DumpHistoryResponse -> f DumpHistoryResponse)
-> (([AnyChainBlock] -> f [AnyChainBlock])
-> Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> ([AnyChainBlock] -> f [AnyChainBlock])
-> DumpHistoryResponse
-> f DumpHistoryResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((DumpHistoryResponse -> Vector AnyChainBlock)
-> (DumpHistoryResponse
-> Vector AnyChainBlock -> DumpHistoryResponse)
-> Lens
DumpHistoryResponse
DumpHistoryResponse
(Vector AnyChainBlock)
(Vector AnyChainBlock)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryResponse -> Vector AnyChainBlock
_DumpHistoryResponse'block
(\ DumpHistoryResponse
x__ Vector AnyChainBlock
y__ -> DumpHistoryResponse
x__ {_DumpHistoryResponse'block = y__}))
((Vector AnyChainBlock -> [AnyChainBlock])
-> (Vector AnyChainBlock
-> [AnyChainBlock] -> Vector AnyChainBlock)
-> Lens
(Vector AnyChainBlock)
(Vector AnyChainBlock)
[AnyChainBlock]
[AnyChainBlock]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector AnyChainBlock -> [AnyChainBlock]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ Vector AnyChainBlock
_ [AnyChainBlock]
y__ -> [AnyChainBlock] -> Vector AnyChainBlock
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [AnyChainBlock]
y__))
instance Data.ProtoLens.Field.HasField DumpHistoryResponse "vec'block" (Data.Vector.Vector AnyChainBlock) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "vec'block"
-> (Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> DumpHistoryResponse
-> f DumpHistoryResponse
fieldOf Proxy# "vec'block"
_
= ((Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> DumpHistoryResponse -> f DumpHistoryResponse)
-> ((Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> (Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> DumpHistoryResponse
-> f DumpHistoryResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((DumpHistoryResponse -> Vector AnyChainBlock)
-> (DumpHistoryResponse
-> Vector AnyChainBlock -> DumpHistoryResponse)
-> Lens
DumpHistoryResponse
DumpHistoryResponse
(Vector AnyChainBlock)
(Vector AnyChainBlock)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryResponse -> Vector AnyChainBlock
_DumpHistoryResponse'block
(\ DumpHistoryResponse
x__ Vector AnyChainBlock
y__ -> DumpHistoryResponse
x__ {_DumpHistoryResponse'block = y__}))
(Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> Vector AnyChainBlock -> f (Vector AnyChainBlock)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField DumpHistoryResponse "nextToken" BlockRef where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "nextToken"
-> (BlockRef -> f BlockRef)
-> DumpHistoryResponse
-> f DumpHistoryResponse
fieldOf Proxy# "nextToken"
_
= ((Maybe BlockRef -> f (Maybe BlockRef))
-> DumpHistoryResponse -> f DumpHistoryResponse)
-> ((BlockRef -> f BlockRef)
-> Maybe BlockRef -> f (Maybe BlockRef))
-> (BlockRef -> f BlockRef)
-> DumpHistoryResponse
-> f DumpHistoryResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((DumpHistoryResponse -> Maybe BlockRef)
-> (DumpHistoryResponse -> Maybe BlockRef -> DumpHistoryResponse)
-> Lens
DumpHistoryResponse
DumpHistoryResponse
(Maybe BlockRef)
(Maybe BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryResponse -> Maybe BlockRef
_DumpHistoryResponse'nextToken
(\ DumpHistoryResponse
x__ Maybe BlockRef
y__ -> DumpHistoryResponse
x__ {_DumpHistoryResponse'nextToken = y__}))
(BlockRef -> Lens' (Maybe BlockRef) BlockRef
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens BlockRef
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField DumpHistoryResponse "maybe'nextToken" (Prelude.Maybe BlockRef) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'nextToken"
-> (Maybe BlockRef -> f (Maybe BlockRef))
-> DumpHistoryResponse
-> f DumpHistoryResponse
fieldOf Proxy# "maybe'nextToken"
_
= ((Maybe BlockRef -> f (Maybe BlockRef))
-> DumpHistoryResponse -> f DumpHistoryResponse)
-> ((Maybe BlockRef -> f (Maybe BlockRef))
-> Maybe BlockRef -> f (Maybe BlockRef))
-> (Maybe BlockRef -> f (Maybe BlockRef))
-> DumpHistoryResponse
-> f DumpHistoryResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((DumpHistoryResponse -> Maybe BlockRef)
-> (DumpHistoryResponse -> Maybe BlockRef -> DumpHistoryResponse)
-> Lens
DumpHistoryResponse
DumpHistoryResponse
(Maybe BlockRef)
(Maybe BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryResponse -> Maybe BlockRef
_DumpHistoryResponse'nextToken
(\ DumpHistoryResponse
x__ Maybe BlockRef
y__ -> DumpHistoryResponse
x__ {_DumpHistoryResponse'nextToken = y__}))
(Maybe BlockRef -> f (Maybe BlockRef))
-> Maybe BlockRef -> f (Maybe BlockRef)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message DumpHistoryResponse where
messageName :: Proxy DumpHistoryResponse -> Text
messageName Proxy DumpHistoryResponse
_
= String -> Text
Data.Text.pack String
"utxorpc.v1alpha.sync.DumpHistoryResponse"
packedMessageDescriptor :: Proxy DumpHistoryResponse -> ByteString
packedMessageDescriptor Proxy DumpHistoryResponse
_
= ByteString
"\n\
\\DC3DumpHistoryResponse\DC29\n\
\\ENQblock\CAN\SOH \ETX(\v2#.utxorpc.v1alpha.sync.AnyChainBlockR\ENQblock\DC2=\n\
\\n\
\next_token\CAN\STX \SOH(\v2\RS.utxorpc.v1alpha.sync.BlockRefR\tnextToken"
packedFileDescriptor :: Proxy DumpHistoryResponse -> ByteString
packedFileDescriptor Proxy DumpHistoryResponse
_ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor DumpHistoryResponse)
fieldsByTag
= let
block__field_descriptor :: FieldDescriptor DumpHistoryResponse
block__field_descriptor
= String
-> FieldTypeDescriptor AnyChainBlock
-> FieldAccessor DumpHistoryResponse AnyChainBlock
-> FieldDescriptor DumpHistoryResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"block"
(MessageOrGroup -> FieldTypeDescriptor AnyChainBlock
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor AnyChainBlock)
(Packing
-> Lens' DumpHistoryResponse [AnyChainBlock]
-> FieldAccessor DumpHistoryResponse AnyChainBlock
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"block")) ::
Data.ProtoLens.FieldDescriptor DumpHistoryResponse
nextToken__field_descriptor :: FieldDescriptor DumpHistoryResponse
nextToken__field_descriptor
= String
-> FieldTypeDescriptor BlockRef
-> FieldAccessor DumpHistoryResponse BlockRef
-> FieldDescriptor DumpHistoryResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"next_token"
(MessageOrGroup -> FieldTypeDescriptor BlockRef
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor BlockRef)
(Lens
DumpHistoryResponse
DumpHistoryResponse
(Maybe BlockRef)
(Maybe BlockRef)
-> FieldAccessor DumpHistoryResponse BlockRef
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'nextToken")) ::
Data.ProtoLens.FieldDescriptor DumpHistoryResponse
in
[(Tag, FieldDescriptor DumpHistoryResponse)]
-> Map Tag (FieldDescriptor DumpHistoryResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor DumpHistoryResponse
block__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor DumpHistoryResponse
nextToken__field_descriptor)]
unknownFields :: Lens' DumpHistoryResponse FieldSet
unknownFields
= (DumpHistoryResponse -> FieldSet)
-> (DumpHistoryResponse -> FieldSet -> DumpHistoryResponse)
-> Lens' DumpHistoryResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
DumpHistoryResponse -> FieldSet
_DumpHistoryResponse'_unknownFields
(\ DumpHistoryResponse
x__ FieldSet
y__ -> DumpHistoryResponse
x__ {_DumpHistoryResponse'_unknownFields = y__})
defMessage :: DumpHistoryResponse
defMessage
= DumpHistoryResponse'_constructor
{_DumpHistoryResponse'block :: Vector AnyChainBlock
_DumpHistoryResponse'block = Vector AnyChainBlock
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_DumpHistoryResponse'nextToken :: Maybe BlockRef
_DumpHistoryResponse'nextToken = Maybe BlockRef
forall a. Maybe a
Prelude.Nothing,
_DumpHistoryResponse'_unknownFields :: FieldSet
_DumpHistoryResponse'_unknownFields = []}
parseMessage :: Parser DumpHistoryResponse
parseMessage
= let
loop ::
DumpHistoryResponse
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld AnyChainBlock
-> Data.ProtoLens.Encoding.Bytes.Parser DumpHistoryResponse
loop :: DumpHistoryResponse
-> Growing Vector RealWorld AnyChainBlock
-> Parser DumpHistoryResponse
loop DumpHistoryResponse
x Growing Vector RealWorld AnyChainBlock
mutable'block
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector AnyChainBlock
frozen'block <- IO (Vector AnyChainBlock) -> Parser (Vector AnyChainBlock)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) AnyChainBlock
-> IO (Vector AnyChainBlock)
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 AnyChainBlock
Growing Vector (PrimState IO) AnyChainBlock
mutable'block)
(let missing :: [a]
missing = []
in
if [Any] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
String
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
DumpHistoryResponse -> Parser DumpHistoryResponse
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter DumpHistoryResponse DumpHistoryResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> DumpHistoryResponse
-> DumpHistoryResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f DumpHistoryResponse FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' DumpHistoryResponse FieldSet
Setter DumpHistoryResponse DumpHistoryResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
DumpHistoryResponse
DumpHistoryResponse
(Vector AnyChainBlock)
(Vector AnyChainBlock)
-> Vector AnyChainBlock
-> DumpHistoryResponse
-> DumpHistoryResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'block") Vector AnyChainBlock
frozen'block DumpHistoryResponse
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
Word64
10
-> do !AnyChainBlock
y <- Parser AnyChainBlock -> String -> Parser AnyChainBlock
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser AnyChainBlock -> Parser AnyChainBlock
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 AnyChainBlock
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"block"
Growing Vector RealWorld AnyChainBlock
v <- IO (Growing Vector RealWorld AnyChainBlock)
-> Parser (Growing Vector RealWorld AnyChainBlock)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) AnyChainBlock
-> AnyChainBlock
-> IO (Growing Vector (PrimState IO) AnyChainBlock)
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 AnyChainBlock
Growing Vector (PrimState IO) AnyChainBlock
mutable'block AnyChainBlock
y)
DumpHistoryResponse
-> Growing Vector RealWorld AnyChainBlock
-> Parser DumpHistoryResponse
loop DumpHistoryResponse
x Growing Vector RealWorld AnyChainBlock
v
Word64
18
-> do BlockRef
y <- Parser BlockRef -> String -> Parser BlockRef
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser BlockRef -> Parser BlockRef
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 BlockRef
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"next_token"
DumpHistoryResponse
-> Growing Vector RealWorld AnyChainBlock
-> Parser DumpHistoryResponse
loop
(Setter DumpHistoryResponse DumpHistoryResponse BlockRef BlockRef
-> BlockRef -> DumpHistoryResponse -> DumpHistoryResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"nextToken") BlockRef
y DumpHistoryResponse
x)
Growing Vector RealWorld AnyChainBlock
mutable'block
Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
DumpHistoryResponse
-> Growing Vector RealWorld AnyChainBlock
-> Parser DumpHistoryResponse
loop
(Setter DumpHistoryResponse DumpHistoryResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> DumpHistoryResponse
-> DumpHistoryResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f DumpHistoryResponse FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' DumpHistoryResponse FieldSet
Setter DumpHistoryResponse DumpHistoryResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) DumpHistoryResponse
x)
Growing Vector RealWorld AnyChainBlock
mutable'block
in
Parser DumpHistoryResponse -> String -> Parser DumpHistoryResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld AnyChainBlock
mutable'block <- IO (Growing Vector RealWorld AnyChainBlock)
-> Parser (Growing Vector RealWorld AnyChainBlock)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld AnyChainBlock)
IO (Growing Vector (PrimState IO) AnyChainBlock)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
DumpHistoryResponse
-> Growing Vector RealWorld AnyChainBlock
-> Parser DumpHistoryResponse
loop DumpHistoryResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld AnyChainBlock
mutable'block)
String
"DumpHistoryResponse"
buildMessage :: DumpHistoryResponse -> Builder
buildMessage
= \ DumpHistoryResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((AnyChainBlock -> Builder) -> Vector AnyChainBlock -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ AnyChainBlock
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
((ByteString -> Builder)
-> (AnyChainBlock -> ByteString) -> AnyChainBlock -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
AnyChainBlock -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage AnyChainBlock
_v))
(FoldLike
(Vector AnyChainBlock)
DumpHistoryResponse
DumpHistoryResponse
(Vector AnyChainBlock)
(Vector AnyChainBlock)
-> DumpHistoryResponse -> Vector AnyChainBlock
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'block") DumpHistoryResponse
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe BlockRef)
DumpHistoryResponse
DumpHistoryResponse
(Maybe BlockRef)
(Maybe BlockRef)
-> DumpHistoryResponse -> Maybe BlockRef
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'nextToken") DumpHistoryResponse
_x
of
Maybe BlockRef
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just BlockRef
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
((ByteString -> Builder)
-> (BlockRef -> ByteString) -> BlockRef -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
BlockRef -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage BlockRef
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet DumpHistoryResponse DumpHistoryResponse FieldSet FieldSet
-> DumpHistoryResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet DumpHistoryResponse DumpHistoryResponse FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' DumpHistoryResponse FieldSet
Data.ProtoLens.unknownFields DumpHistoryResponse
_x)))
instance Control.DeepSeq.NFData DumpHistoryResponse where
rnf :: DumpHistoryResponse -> ()
rnf
= \ DumpHistoryResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(DumpHistoryResponse -> FieldSet
_DumpHistoryResponse'_unknownFields DumpHistoryResponse
x__)
(Vector AnyChainBlock -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(DumpHistoryResponse -> Vector AnyChainBlock
_DumpHistoryResponse'block DumpHistoryResponse
x__)
(Maybe BlockRef -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (DumpHistoryResponse -> Maybe BlockRef
_DumpHistoryResponse'nextToken DumpHistoryResponse
x__) ()))
data FetchBlockRequest
= FetchBlockRequest'_constructor {FetchBlockRequest -> Vector BlockRef
_FetchBlockRequest'ref :: !(Data.Vector.Vector BlockRef),
FetchBlockRequest -> Maybe FieldMask
_FetchBlockRequest'fieldMask :: !(Prelude.Maybe Proto.Google.Protobuf.FieldMask.FieldMask),
FetchBlockRequest -> FieldSet
_FetchBlockRequest'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (FetchBlockRequest -> FetchBlockRequest -> Bool
(FetchBlockRequest -> FetchBlockRequest -> Bool)
-> (FetchBlockRequest -> FetchBlockRequest -> Bool)
-> Eq FetchBlockRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FetchBlockRequest -> FetchBlockRequest -> Bool
== :: FetchBlockRequest -> FetchBlockRequest -> Bool
$c/= :: FetchBlockRequest -> FetchBlockRequest -> Bool
/= :: FetchBlockRequest -> FetchBlockRequest -> Bool
Prelude.Eq, Eq FetchBlockRequest
Eq FetchBlockRequest =>
(FetchBlockRequest -> FetchBlockRequest -> Ordering)
-> (FetchBlockRequest -> FetchBlockRequest -> Bool)
-> (FetchBlockRequest -> FetchBlockRequest -> Bool)
-> (FetchBlockRequest -> FetchBlockRequest -> Bool)
-> (FetchBlockRequest -> FetchBlockRequest -> Bool)
-> (FetchBlockRequest -> FetchBlockRequest -> FetchBlockRequest)
-> (FetchBlockRequest -> FetchBlockRequest -> FetchBlockRequest)
-> Ord FetchBlockRequest
FetchBlockRequest -> FetchBlockRequest -> Bool
FetchBlockRequest -> FetchBlockRequest -> Ordering
FetchBlockRequest -> FetchBlockRequest -> FetchBlockRequest
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
$ccompare :: FetchBlockRequest -> FetchBlockRequest -> Ordering
compare :: FetchBlockRequest -> FetchBlockRequest -> Ordering
$c< :: FetchBlockRequest -> FetchBlockRequest -> Bool
< :: FetchBlockRequest -> FetchBlockRequest -> Bool
$c<= :: FetchBlockRequest -> FetchBlockRequest -> Bool
<= :: FetchBlockRequest -> FetchBlockRequest -> Bool
$c> :: FetchBlockRequest -> FetchBlockRequest -> Bool
> :: FetchBlockRequest -> FetchBlockRequest -> Bool
$c>= :: FetchBlockRequest -> FetchBlockRequest -> Bool
>= :: FetchBlockRequest -> FetchBlockRequest -> Bool
$cmax :: FetchBlockRequest -> FetchBlockRequest -> FetchBlockRequest
max :: FetchBlockRequest -> FetchBlockRequest -> FetchBlockRequest
$cmin :: FetchBlockRequest -> FetchBlockRequest -> FetchBlockRequest
min :: FetchBlockRequest -> FetchBlockRequest -> FetchBlockRequest
Prelude.Ord)
instance Prelude.Show FetchBlockRequest where
showsPrec :: Int -> FetchBlockRequest -> ShowS
showsPrec Int
_ FetchBlockRequest
__x String
__s
= Char -> ShowS
Prelude.showChar
Char
'{'
(String -> ShowS
Prelude.showString
(FetchBlockRequest -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort FetchBlockRequest
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField FetchBlockRequest "ref" [BlockRef] where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "ref"
-> ([BlockRef] -> f [BlockRef])
-> FetchBlockRequest
-> f FetchBlockRequest
fieldOf Proxy# "ref"
_
= ((Vector BlockRef -> f (Vector BlockRef))
-> FetchBlockRequest -> f FetchBlockRequest)
-> (([BlockRef] -> f [BlockRef])
-> Vector BlockRef -> f (Vector BlockRef))
-> ([BlockRef] -> f [BlockRef])
-> FetchBlockRequest
-> f FetchBlockRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FetchBlockRequest -> Vector BlockRef)
-> (FetchBlockRequest -> Vector BlockRef -> FetchBlockRequest)
-> Lens
FetchBlockRequest
FetchBlockRequest
(Vector BlockRef)
(Vector BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FetchBlockRequest -> Vector BlockRef
_FetchBlockRequest'ref
(\ FetchBlockRequest
x__ Vector BlockRef
y__ -> FetchBlockRequest
x__ {_FetchBlockRequest'ref = y__}))
((Vector BlockRef -> [BlockRef])
-> (Vector BlockRef -> [BlockRef] -> Vector BlockRef)
-> Lens (Vector BlockRef) (Vector BlockRef) [BlockRef] [BlockRef]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector BlockRef -> [BlockRef]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ Vector BlockRef
_ [BlockRef]
y__ -> [BlockRef] -> Vector BlockRef
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [BlockRef]
y__))
instance Data.ProtoLens.Field.HasField FetchBlockRequest "vec'ref" (Data.Vector.Vector BlockRef) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "vec'ref"
-> (Vector BlockRef -> f (Vector BlockRef))
-> FetchBlockRequest
-> f FetchBlockRequest
fieldOf Proxy# "vec'ref"
_
= ((Vector BlockRef -> f (Vector BlockRef))
-> FetchBlockRequest -> f FetchBlockRequest)
-> ((Vector BlockRef -> f (Vector BlockRef))
-> Vector BlockRef -> f (Vector BlockRef))
-> (Vector BlockRef -> f (Vector BlockRef))
-> FetchBlockRequest
-> f FetchBlockRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FetchBlockRequest -> Vector BlockRef)
-> (FetchBlockRequest -> Vector BlockRef -> FetchBlockRequest)
-> Lens
FetchBlockRequest
FetchBlockRequest
(Vector BlockRef)
(Vector BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FetchBlockRequest -> Vector BlockRef
_FetchBlockRequest'ref
(\ FetchBlockRequest
x__ Vector BlockRef
y__ -> FetchBlockRequest
x__ {_FetchBlockRequest'ref = y__}))
(Vector BlockRef -> f (Vector BlockRef))
-> Vector BlockRef -> f (Vector BlockRef)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField FetchBlockRequest "fieldMask" Proto.Google.Protobuf.FieldMask.FieldMask where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "fieldMask"
-> (FieldMask -> f FieldMask)
-> FetchBlockRequest
-> f FetchBlockRequest
fieldOf Proxy# "fieldMask"
_
= ((Maybe FieldMask -> f (Maybe FieldMask))
-> FetchBlockRequest -> f FetchBlockRequest)
-> ((FieldMask -> f FieldMask)
-> Maybe FieldMask -> f (Maybe FieldMask))
-> (FieldMask -> f FieldMask)
-> FetchBlockRequest
-> f FetchBlockRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FetchBlockRequest -> Maybe FieldMask)
-> (FetchBlockRequest -> Maybe FieldMask -> FetchBlockRequest)
-> Lens
FetchBlockRequest
FetchBlockRequest
(Maybe FieldMask)
(Maybe FieldMask)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FetchBlockRequest -> Maybe FieldMask
_FetchBlockRequest'fieldMask
(\ FetchBlockRequest
x__ Maybe FieldMask
y__ -> FetchBlockRequest
x__ {_FetchBlockRequest'fieldMask = y__}))
(FieldMask -> Lens' (Maybe FieldMask) FieldMask
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens FieldMask
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField FetchBlockRequest "maybe'fieldMask" (Prelude.Maybe Proto.Google.Protobuf.FieldMask.FieldMask) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'fieldMask"
-> (Maybe FieldMask -> f (Maybe FieldMask))
-> FetchBlockRequest
-> f FetchBlockRequest
fieldOf Proxy# "maybe'fieldMask"
_
= ((Maybe FieldMask -> f (Maybe FieldMask))
-> FetchBlockRequest -> f FetchBlockRequest)
-> ((Maybe FieldMask -> f (Maybe FieldMask))
-> Maybe FieldMask -> f (Maybe FieldMask))
-> (Maybe FieldMask -> f (Maybe FieldMask))
-> FetchBlockRequest
-> f FetchBlockRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FetchBlockRequest -> Maybe FieldMask)
-> (FetchBlockRequest -> Maybe FieldMask -> FetchBlockRequest)
-> Lens
FetchBlockRequest
FetchBlockRequest
(Maybe FieldMask)
(Maybe FieldMask)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FetchBlockRequest -> Maybe FieldMask
_FetchBlockRequest'fieldMask
(\ FetchBlockRequest
x__ Maybe FieldMask
y__ -> FetchBlockRequest
x__ {_FetchBlockRequest'fieldMask = y__}))
(Maybe FieldMask -> f (Maybe FieldMask))
-> Maybe FieldMask -> f (Maybe FieldMask)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message FetchBlockRequest where
messageName :: Proxy FetchBlockRequest -> Text
messageName Proxy FetchBlockRequest
_
= String -> Text
Data.Text.pack String
"utxorpc.v1alpha.sync.FetchBlockRequest"
packedMessageDescriptor :: Proxy FetchBlockRequest -> ByteString
packedMessageDescriptor Proxy FetchBlockRequest
_
= ByteString
"\n\
\\DC1FetchBlockRequest\DC20\n\
\\ETXref\CAN\SOH \ETX(\v2\RS.utxorpc.v1alpha.sync.BlockRefR\ETXref\DC29\n\
\\n\
\field_mask\CAN\STX \SOH(\v2\SUB.google.protobuf.FieldMaskR\tfieldMask"
packedFileDescriptor :: Proxy FetchBlockRequest -> ByteString
packedFileDescriptor Proxy FetchBlockRequest
_ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor FetchBlockRequest)
fieldsByTag
= let
ref__field_descriptor :: FieldDescriptor FetchBlockRequest
ref__field_descriptor
= String
-> FieldTypeDescriptor BlockRef
-> FieldAccessor FetchBlockRequest BlockRef
-> FieldDescriptor FetchBlockRequest
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"ref"
(MessageOrGroup -> FieldTypeDescriptor BlockRef
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor BlockRef)
(Packing
-> Lens' FetchBlockRequest [BlockRef]
-> FieldAccessor FetchBlockRequest BlockRef
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"ref")) ::
Data.ProtoLens.FieldDescriptor FetchBlockRequest
fieldMask__field_descriptor :: FieldDescriptor FetchBlockRequest
fieldMask__field_descriptor
= String
-> FieldTypeDescriptor FieldMask
-> FieldAccessor FetchBlockRequest FieldMask
-> FieldDescriptor FetchBlockRequest
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"field_mask"
(MessageOrGroup -> FieldTypeDescriptor FieldMask
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Proto.Google.Protobuf.FieldMask.FieldMask)
(Lens
FetchBlockRequest
FetchBlockRequest
(Maybe FieldMask)
(Maybe FieldMask)
-> FieldAccessor FetchBlockRequest FieldMask
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'fieldMask")) ::
Data.ProtoLens.FieldDescriptor FetchBlockRequest
in
[(Tag, FieldDescriptor FetchBlockRequest)]
-> Map Tag (FieldDescriptor FetchBlockRequest)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor FetchBlockRequest
ref__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor FetchBlockRequest
fieldMask__field_descriptor)]
unknownFields :: Lens' FetchBlockRequest FieldSet
unknownFields
= (FetchBlockRequest -> FieldSet)
-> (FetchBlockRequest -> FieldSet -> FetchBlockRequest)
-> Lens' FetchBlockRequest FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FetchBlockRequest -> FieldSet
_FetchBlockRequest'_unknownFields
(\ FetchBlockRequest
x__ FieldSet
y__ -> FetchBlockRequest
x__ {_FetchBlockRequest'_unknownFields = y__})
defMessage :: FetchBlockRequest
defMessage
= FetchBlockRequest'_constructor
{_FetchBlockRequest'ref :: Vector BlockRef
_FetchBlockRequest'ref = Vector BlockRef
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_FetchBlockRequest'fieldMask :: Maybe FieldMask
_FetchBlockRequest'fieldMask = Maybe FieldMask
forall a. Maybe a
Prelude.Nothing,
_FetchBlockRequest'_unknownFields :: FieldSet
_FetchBlockRequest'_unknownFields = []}
parseMessage :: Parser FetchBlockRequest
parseMessage
= let
loop ::
FetchBlockRequest
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld BlockRef
-> Data.ProtoLens.Encoding.Bytes.Parser FetchBlockRequest
loop :: FetchBlockRequest
-> Growing Vector RealWorld BlockRef -> Parser FetchBlockRequest
loop FetchBlockRequest
x Growing Vector RealWorld BlockRef
mutable'ref
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector BlockRef
frozen'ref <- IO (Vector BlockRef) -> Parser (Vector BlockRef)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) BlockRef -> IO (Vector BlockRef)
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 BlockRef
Growing Vector (PrimState IO) BlockRef
mutable'ref)
(let missing :: [a]
missing = []
in
if [Any] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
String
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
FetchBlockRequest -> Parser FetchBlockRequest
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter FetchBlockRequest FetchBlockRequest FieldSet FieldSet
-> (FieldSet -> FieldSet) -> FetchBlockRequest -> FetchBlockRequest
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f FetchBlockRequest FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FetchBlockRequest FieldSet
Setter FetchBlockRequest FetchBlockRequest FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
FetchBlockRequest
FetchBlockRequest
(Vector BlockRef)
(Vector BlockRef)
-> Vector BlockRef -> FetchBlockRequest -> FetchBlockRequest
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'ref") Vector BlockRef
frozen'ref FetchBlockRequest
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
Word64
10
-> do !BlockRef
y <- Parser BlockRef -> String -> Parser BlockRef
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser BlockRef -> Parser BlockRef
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 BlockRef
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"ref"
Growing Vector RealWorld BlockRef
v <- IO (Growing Vector RealWorld BlockRef)
-> Parser (Growing Vector RealWorld BlockRef)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) BlockRef
-> BlockRef -> IO (Growing Vector (PrimState IO) BlockRef)
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 BlockRef
Growing Vector (PrimState IO) BlockRef
mutable'ref BlockRef
y)
FetchBlockRequest
-> Growing Vector RealWorld BlockRef -> Parser FetchBlockRequest
loop FetchBlockRequest
x Growing Vector RealWorld BlockRef
v
Word64
18
-> do FieldMask
y <- Parser FieldMask -> String -> Parser FieldMask
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser FieldMask -> Parser FieldMask
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 FieldMask
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"field_mask"
FetchBlockRequest
-> Growing Vector RealWorld BlockRef -> Parser FetchBlockRequest
loop
(Setter FetchBlockRequest FetchBlockRequest FieldMask FieldMask
-> FieldMask -> FetchBlockRequest -> FetchBlockRequest
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"fieldMask") FieldMask
y FetchBlockRequest
x)
Growing Vector RealWorld BlockRef
mutable'ref
Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
FetchBlockRequest
-> Growing Vector RealWorld BlockRef -> Parser FetchBlockRequest
loop
(Setter FetchBlockRequest FetchBlockRequest FieldSet FieldSet
-> (FieldSet -> FieldSet) -> FetchBlockRequest -> FetchBlockRequest
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f FetchBlockRequest FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FetchBlockRequest FieldSet
Setter FetchBlockRequest FetchBlockRequest FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) FetchBlockRequest
x)
Growing Vector RealWorld BlockRef
mutable'ref
in
Parser FetchBlockRequest -> String -> Parser FetchBlockRequest
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld BlockRef
mutable'ref <- IO (Growing Vector RealWorld BlockRef)
-> Parser (Growing Vector RealWorld BlockRef)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld BlockRef)
IO (Growing Vector (PrimState IO) BlockRef)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
FetchBlockRequest
-> Growing Vector RealWorld BlockRef -> Parser FetchBlockRequest
loop FetchBlockRequest
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld BlockRef
mutable'ref)
String
"FetchBlockRequest"
buildMessage :: FetchBlockRequest -> Builder
buildMessage
= \ FetchBlockRequest
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((BlockRef -> Builder) -> Vector BlockRef -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ BlockRef
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
((ByteString -> Builder)
-> (BlockRef -> ByteString) -> BlockRef -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
BlockRef -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage BlockRef
_v))
(FoldLike
(Vector BlockRef)
FetchBlockRequest
FetchBlockRequest
(Vector BlockRef)
(Vector BlockRef)
-> FetchBlockRequest -> Vector BlockRef
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'ref") FetchBlockRequest
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe FieldMask)
FetchBlockRequest
FetchBlockRequest
(Maybe FieldMask)
(Maybe FieldMask)
-> FetchBlockRequest -> Maybe FieldMask
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'fieldMask") FetchBlockRequest
_x
of
Maybe FieldMask
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just FieldMask
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
((ByteString -> Builder)
-> (FieldMask -> ByteString) -> FieldMask -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
FieldMask -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage FieldMask
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet FetchBlockRequest FetchBlockRequest FieldSet FieldSet
-> FetchBlockRequest -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet FetchBlockRequest FetchBlockRequest FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FetchBlockRequest FieldSet
Data.ProtoLens.unknownFields FetchBlockRequest
_x)))
instance Control.DeepSeq.NFData FetchBlockRequest where
rnf :: FetchBlockRequest -> ()
rnf
= \ FetchBlockRequest
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(FetchBlockRequest -> FieldSet
_FetchBlockRequest'_unknownFields FetchBlockRequest
x__)
(Vector BlockRef -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(FetchBlockRequest -> Vector BlockRef
_FetchBlockRequest'ref FetchBlockRequest
x__)
(Maybe FieldMask -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (FetchBlockRequest -> Maybe FieldMask
_FetchBlockRequest'fieldMask FetchBlockRequest
x__) ()))
data FetchBlockResponse
= FetchBlockResponse'_constructor {FetchBlockResponse -> Vector AnyChainBlock
_FetchBlockResponse'block :: !(Data.Vector.Vector AnyChainBlock),
FetchBlockResponse -> FieldSet
_FetchBlockResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (FetchBlockResponse -> FetchBlockResponse -> Bool
(FetchBlockResponse -> FetchBlockResponse -> Bool)
-> (FetchBlockResponse -> FetchBlockResponse -> Bool)
-> Eq FetchBlockResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FetchBlockResponse -> FetchBlockResponse -> Bool
== :: FetchBlockResponse -> FetchBlockResponse -> Bool
$c/= :: FetchBlockResponse -> FetchBlockResponse -> Bool
/= :: FetchBlockResponse -> FetchBlockResponse -> Bool
Prelude.Eq, Eq FetchBlockResponse
Eq FetchBlockResponse =>
(FetchBlockResponse -> FetchBlockResponse -> Ordering)
-> (FetchBlockResponse -> FetchBlockResponse -> Bool)
-> (FetchBlockResponse -> FetchBlockResponse -> Bool)
-> (FetchBlockResponse -> FetchBlockResponse -> Bool)
-> (FetchBlockResponse -> FetchBlockResponse -> Bool)
-> (FetchBlockResponse -> FetchBlockResponse -> FetchBlockResponse)
-> (FetchBlockResponse -> FetchBlockResponse -> FetchBlockResponse)
-> Ord FetchBlockResponse
FetchBlockResponse -> FetchBlockResponse -> Bool
FetchBlockResponse -> FetchBlockResponse -> Ordering
FetchBlockResponse -> FetchBlockResponse -> FetchBlockResponse
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
$ccompare :: FetchBlockResponse -> FetchBlockResponse -> Ordering
compare :: FetchBlockResponse -> FetchBlockResponse -> Ordering
$c< :: FetchBlockResponse -> FetchBlockResponse -> Bool
< :: FetchBlockResponse -> FetchBlockResponse -> Bool
$c<= :: FetchBlockResponse -> FetchBlockResponse -> Bool
<= :: FetchBlockResponse -> FetchBlockResponse -> Bool
$c> :: FetchBlockResponse -> FetchBlockResponse -> Bool
> :: FetchBlockResponse -> FetchBlockResponse -> Bool
$c>= :: FetchBlockResponse -> FetchBlockResponse -> Bool
>= :: FetchBlockResponse -> FetchBlockResponse -> Bool
$cmax :: FetchBlockResponse -> FetchBlockResponse -> FetchBlockResponse
max :: FetchBlockResponse -> FetchBlockResponse -> FetchBlockResponse
$cmin :: FetchBlockResponse -> FetchBlockResponse -> FetchBlockResponse
min :: FetchBlockResponse -> FetchBlockResponse -> FetchBlockResponse
Prelude.Ord)
instance Prelude.Show FetchBlockResponse where
showsPrec :: Int -> FetchBlockResponse -> ShowS
showsPrec Int
_ FetchBlockResponse
__x String
__s
= Char -> ShowS
Prelude.showChar
Char
'{'
(String -> ShowS
Prelude.showString
(FetchBlockResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort FetchBlockResponse
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField FetchBlockResponse "block" [AnyChainBlock] where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "block"
-> ([AnyChainBlock] -> f [AnyChainBlock])
-> FetchBlockResponse
-> f FetchBlockResponse
fieldOf Proxy# "block"
_
= ((Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> FetchBlockResponse -> f FetchBlockResponse)
-> (([AnyChainBlock] -> f [AnyChainBlock])
-> Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> ([AnyChainBlock] -> f [AnyChainBlock])
-> FetchBlockResponse
-> f FetchBlockResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FetchBlockResponse -> Vector AnyChainBlock)
-> (FetchBlockResponse
-> Vector AnyChainBlock -> FetchBlockResponse)
-> Lens
FetchBlockResponse
FetchBlockResponse
(Vector AnyChainBlock)
(Vector AnyChainBlock)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FetchBlockResponse -> Vector AnyChainBlock
_FetchBlockResponse'block
(\ FetchBlockResponse
x__ Vector AnyChainBlock
y__ -> FetchBlockResponse
x__ {_FetchBlockResponse'block = y__}))
((Vector AnyChainBlock -> [AnyChainBlock])
-> (Vector AnyChainBlock
-> [AnyChainBlock] -> Vector AnyChainBlock)
-> Lens
(Vector AnyChainBlock)
(Vector AnyChainBlock)
[AnyChainBlock]
[AnyChainBlock]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector AnyChainBlock -> [AnyChainBlock]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ Vector AnyChainBlock
_ [AnyChainBlock]
y__ -> [AnyChainBlock] -> Vector AnyChainBlock
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [AnyChainBlock]
y__))
instance Data.ProtoLens.Field.HasField FetchBlockResponse "vec'block" (Data.Vector.Vector AnyChainBlock) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "vec'block"
-> (Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> FetchBlockResponse
-> f FetchBlockResponse
fieldOf Proxy# "vec'block"
_
= ((Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> FetchBlockResponse -> f FetchBlockResponse)
-> ((Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> (Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> FetchBlockResponse
-> f FetchBlockResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FetchBlockResponse -> Vector AnyChainBlock)
-> (FetchBlockResponse
-> Vector AnyChainBlock -> FetchBlockResponse)
-> Lens
FetchBlockResponse
FetchBlockResponse
(Vector AnyChainBlock)
(Vector AnyChainBlock)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FetchBlockResponse -> Vector AnyChainBlock
_FetchBlockResponse'block
(\ FetchBlockResponse
x__ Vector AnyChainBlock
y__ -> FetchBlockResponse
x__ {_FetchBlockResponse'block = y__}))
(Vector AnyChainBlock -> f (Vector AnyChainBlock))
-> Vector AnyChainBlock -> f (Vector AnyChainBlock)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message FetchBlockResponse where
messageName :: Proxy FetchBlockResponse -> Text
messageName Proxy FetchBlockResponse
_
= String -> Text
Data.Text.pack String
"utxorpc.v1alpha.sync.FetchBlockResponse"
packedMessageDescriptor :: Proxy FetchBlockResponse -> ByteString
packedMessageDescriptor Proxy FetchBlockResponse
_
= ByteString
"\n\
\\DC2FetchBlockResponse\DC29\n\
\\ENQblock\CAN\SOH \ETX(\v2#.utxorpc.v1alpha.sync.AnyChainBlockR\ENQblock"
packedFileDescriptor :: Proxy FetchBlockResponse -> ByteString
packedFileDescriptor Proxy FetchBlockResponse
_ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor FetchBlockResponse)
fieldsByTag
= let
block__field_descriptor :: FieldDescriptor FetchBlockResponse
block__field_descriptor
= String
-> FieldTypeDescriptor AnyChainBlock
-> FieldAccessor FetchBlockResponse AnyChainBlock
-> FieldDescriptor FetchBlockResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"block"
(MessageOrGroup -> FieldTypeDescriptor AnyChainBlock
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor AnyChainBlock)
(Packing
-> Lens' FetchBlockResponse [AnyChainBlock]
-> FieldAccessor FetchBlockResponse AnyChainBlock
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"block")) ::
Data.ProtoLens.FieldDescriptor FetchBlockResponse
in
[(Tag, FieldDescriptor FetchBlockResponse)]
-> Map Tag (FieldDescriptor FetchBlockResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList [(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor FetchBlockResponse
block__field_descriptor)]
unknownFields :: Lens' FetchBlockResponse FieldSet
unknownFields
= (FetchBlockResponse -> FieldSet)
-> (FetchBlockResponse -> FieldSet -> FetchBlockResponse)
-> Lens' FetchBlockResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FetchBlockResponse -> FieldSet
_FetchBlockResponse'_unknownFields
(\ FetchBlockResponse
x__ FieldSet
y__ -> FetchBlockResponse
x__ {_FetchBlockResponse'_unknownFields = y__})
defMessage :: FetchBlockResponse
defMessage
= FetchBlockResponse'_constructor
{_FetchBlockResponse'block :: Vector AnyChainBlock
_FetchBlockResponse'block = Vector AnyChainBlock
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_FetchBlockResponse'_unknownFields :: FieldSet
_FetchBlockResponse'_unknownFields = []}
parseMessage :: Parser FetchBlockResponse
parseMessage
= let
loop ::
FetchBlockResponse
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld AnyChainBlock
-> Data.ProtoLens.Encoding.Bytes.Parser FetchBlockResponse
loop :: FetchBlockResponse
-> Growing Vector RealWorld AnyChainBlock
-> Parser FetchBlockResponse
loop FetchBlockResponse
x Growing Vector RealWorld AnyChainBlock
mutable'block
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector AnyChainBlock
frozen'block <- IO (Vector AnyChainBlock) -> Parser (Vector AnyChainBlock)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) AnyChainBlock
-> IO (Vector AnyChainBlock)
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 AnyChainBlock
Growing Vector (PrimState IO) AnyChainBlock
mutable'block)
(let missing :: [a]
missing = []
in
if [Any] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
String
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
FetchBlockResponse -> Parser FetchBlockResponse
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter FetchBlockResponse FetchBlockResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> FetchBlockResponse
-> FetchBlockResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f FetchBlockResponse FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FetchBlockResponse FieldSet
Setter FetchBlockResponse FetchBlockResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
FetchBlockResponse
FetchBlockResponse
(Vector AnyChainBlock)
(Vector AnyChainBlock)
-> Vector AnyChainBlock -> FetchBlockResponse -> FetchBlockResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'block") Vector AnyChainBlock
frozen'block FetchBlockResponse
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
Word64
10
-> do !AnyChainBlock
y <- Parser AnyChainBlock -> String -> Parser AnyChainBlock
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser AnyChainBlock -> Parser AnyChainBlock
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 AnyChainBlock
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"block"
Growing Vector RealWorld AnyChainBlock
v <- IO (Growing Vector RealWorld AnyChainBlock)
-> Parser (Growing Vector RealWorld AnyChainBlock)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) AnyChainBlock
-> AnyChainBlock
-> IO (Growing Vector (PrimState IO) AnyChainBlock)
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 AnyChainBlock
Growing Vector (PrimState IO) AnyChainBlock
mutable'block AnyChainBlock
y)
FetchBlockResponse
-> Growing Vector RealWorld AnyChainBlock
-> Parser FetchBlockResponse
loop FetchBlockResponse
x Growing Vector RealWorld AnyChainBlock
v
Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
FetchBlockResponse
-> Growing Vector RealWorld AnyChainBlock
-> Parser FetchBlockResponse
loop
(Setter FetchBlockResponse FetchBlockResponse FieldSet FieldSet
-> (FieldSet -> FieldSet)
-> FetchBlockResponse
-> FetchBlockResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f FetchBlockResponse FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FetchBlockResponse FieldSet
Setter FetchBlockResponse FetchBlockResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) FetchBlockResponse
x)
Growing Vector RealWorld AnyChainBlock
mutable'block
in
Parser FetchBlockResponse -> String -> Parser FetchBlockResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld AnyChainBlock
mutable'block <- IO (Growing Vector RealWorld AnyChainBlock)
-> Parser (Growing Vector RealWorld AnyChainBlock)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld AnyChainBlock)
IO (Growing Vector (PrimState IO) AnyChainBlock)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
FetchBlockResponse
-> Growing Vector RealWorld AnyChainBlock
-> Parser FetchBlockResponse
loop FetchBlockResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld AnyChainBlock
mutable'block)
String
"FetchBlockResponse"
buildMessage :: FetchBlockResponse -> Builder
buildMessage
= \ FetchBlockResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((AnyChainBlock -> Builder) -> Vector AnyChainBlock -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ AnyChainBlock
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
((ByteString -> Builder)
-> (AnyChainBlock -> ByteString) -> AnyChainBlock -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
AnyChainBlock -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage AnyChainBlock
_v))
(FoldLike
(Vector AnyChainBlock)
FetchBlockResponse
FetchBlockResponse
(Vector AnyChainBlock)
(Vector AnyChainBlock)
-> FetchBlockResponse -> Vector AnyChainBlock
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'block") FetchBlockResponse
_x))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet FetchBlockResponse FetchBlockResponse FieldSet FieldSet
-> FetchBlockResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet FetchBlockResponse FetchBlockResponse FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FetchBlockResponse FieldSet
Data.ProtoLens.unknownFields FetchBlockResponse
_x))
instance Control.DeepSeq.NFData FetchBlockResponse where
rnf :: FetchBlockResponse -> ()
rnf
= \ FetchBlockResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(FetchBlockResponse -> FieldSet
_FetchBlockResponse'_unknownFields FetchBlockResponse
x__)
(Vector AnyChainBlock -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (FetchBlockResponse -> Vector AnyChainBlock
_FetchBlockResponse'block FetchBlockResponse
x__) ())
data FollowTipRequest
= FollowTipRequest'_constructor {FollowTipRequest -> Vector BlockRef
_FollowTipRequest'intersect :: !(Data.Vector.Vector BlockRef),
FollowTipRequest -> Maybe FieldMask
_FollowTipRequest'fieldMask :: !(Prelude.Maybe Proto.Google.Protobuf.FieldMask.FieldMask),
FollowTipRequest -> FieldSet
_FollowTipRequest'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (FollowTipRequest -> FollowTipRequest -> Bool
(FollowTipRequest -> FollowTipRequest -> Bool)
-> (FollowTipRequest -> FollowTipRequest -> Bool)
-> Eq FollowTipRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FollowTipRequest -> FollowTipRequest -> Bool
== :: FollowTipRequest -> FollowTipRequest -> Bool
$c/= :: FollowTipRequest -> FollowTipRequest -> Bool
/= :: FollowTipRequest -> FollowTipRequest -> Bool
Prelude.Eq, Eq FollowTipRequest
Eq FollowTipRequest =>
(FollowTipRequest -> FollowTipRequest -> Ordering)
-> (FollowTipRequest -> FollowTipRequest -> Bool)
-> (FollowTipRequest -> FollowTipRequest -> Bool)
-> (FollowTipRequest -> FollowTipRequest -> Bool)
-> (FollowTipRequest -> FollowTipRequest -> Bool)
-> (FollowTipRequest -> FollowTipRequest -> FollowTipRequest)
-> (FollowTipRequest -> FollowTipRequest -> FollowTipRequest)
-> Ord FollowTipRequest
FollowTipRequest -> FollowTipRequest -> Bool
FollowTipRequest -> FollowTipRequest -> Ordering
FollowTipRequest -> FollowTipRequest -> FollowTipRequest
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
$ccompare :: FollowTipRequest -> FollowTipRequest -> Ordering
compare :: FollowTipRequest -> FollowTipRequest -> Ordering
$c< :: FollowTipRequest -> FollowTipRequest -> Bool
< :: FollowTipRequest -> FollowTipRequest -> Bool
$c<= :: FollowTipRequest -> FollowTipRequest -> Bool
<= :: FollowTipRequest -> FollowTipRequest -> Bool
$c> :: FollowTipRequest -> FollowTipRequest -> Bool
> :: FollowTipRequest -> FollowTipRequest -> Bool
$c>= :: FollowTipRequest -> FollowTipRequest -> Bool
>= :: FollowTipRequest -> FollowTipRequest -> Bool
$cmax :: FollowTipRequest -> FollowTipRequest -> FollowTipRequest
max :: FollowTipRequest -> FollowTipRequest -> FollowTipRequest
$cmin :: FollowTipRequest -> FollowTipRequest -> FollowTipRequest
min :: FollowTipRequest -> FollowTipRequest -> FollowTipRequest
Prelude.Ord)
instance Prelude.Show FollowTipRequest where
showsPrec :: Int -> FollowTipRequest -> ShowS
showsPrec Int
_ FollowTipRequest
__x String
__s
= Char -> ShowS
Prelude.showChar
Char
'{'
(String -> ShowS
Prelude.showString
(FollowTipRequest -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort FollowTipRequest
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
instance Data.ProtoLens.Field.HasField FollowTipRequest "intersect" [BlockRef] where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "intersect"
-> ([BlockRef] -> f [BlockRef])
-> FollowTipRequest
-> f FollowTipRequest
fieldOf Proxy# "intersect"
_
= ((Vector BlockRef -> f (Vector BlockRef))
-> FollowTipRequest -> f FollowTipRequest)
-> (([BlockRef] -> f [BlockRef])
-> Vector BlockRef -> f (Vector BlockRef))
-> ([BlockRef] -> f [BlockRef])
-> FollowTipRequest
-> f FollowTipRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipRequest -> Vector BlockRef)
-> (FollowTipRequest -> Vector BlockRef -> FollowTipRequest)
-> Lens
FollowTipRequest
FollowTipRequest
(Vector BlockRef)
(Vector BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipRequest -> Vector BlockRef
_FollowTipRequest'intersect
(\ FollowTipRequest
x__ Vector BlockRef
y__ -> FollowTipRequest
x__ {_FollowTipRequest'intersect = y__}))
((Vector BlockRef -> [BlockRef])
-> (Vector BlockRef -> [BlockRef] -> Vector BlockRef)
-> Lens (Vector BlockRef) (Vector BlockRef) [BlockRef] [BlockRef]
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
Vector BlockRef -> [BlockRef]
forall (v :: * -> *) a. Vector v a => v a -> [a]
Data.Vector.Generic.toList
(\ Vector BlockRef
_ [BlockRef]
y__ -> [BlockRef] -> Vector BlockRef
forall (v :: * -> *) a. Vector v a => [a] -> v a
Data.Vector.Generic.fromList [BlockRef]
y__))
instance Data.ProtoLens.Field.HasField FollowTipRequest "vec'intersect" (Data.Vector.Vector BlockRef) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "vec'intersect"
-> (Vector BlockRef -> f (Vector BlockRef))
-> FollowTipRequest
-> f FollowTipRequest
fieldOf Proxy# "vec'intersect"
_
= ((Vector BlockRef -> f (Vector BlockRef))
-> FollowTipRequest -> f FollowTipRequest)
-> ((Vector BlockRef -> f (Vector BlockRef))
-> Vector BlockRef -> f (Vector BlockRef))
-> (Vector BlockRef -> f (Vector BlockRef))
-> FollowTipRequest
-> f FollowTipRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipRequest -> Vector BlockRef)
-> (FollowTipRequest -> Vector BlockRef -> FollowTipRequest)
-> Lens
FollowTipRequest
FollowTipRequest
(Vector BlockRef)
(Vector BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipRequest -> Vector BlockRef
_FollowTipRequest'intersect
(\ FollowTipRequest
x__ Vector BlockRef
y__ -> FollowTipRequest
x__ {_FollowTipRequest'intersect = y__}))
(Vector BlockRef -> f (Vector BlockRef))
-> Vector BlockRef -> f (Vector BlockRef)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField FollowTipRequest "fieldMask" Proto.Google.Protobuf.FieldMask.FieldMask where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "fieldMask"
-> (FieldMask -> f FieldMask)
-> FollowTipRequest
-> f FollowTipRequest
fieldOf Proxy# "fieldMask"
_
= ((Maybe FieldMask -> f (Maybe FieldMask))
-> FollowTipRequest -> f FollowTipRequest)
-> ((FieldMask -> f FieldMask)
-> Maybe FieldMask -> f (Maybe FieldMask))
-> (FieldMask -> f FieldMask)
-> FollowTipRequest
-> f FollowTipRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipRequest -> Maybe FieldMask)
-> (FollowTipRequest -> Maybe FieldMask -> FollowTipRequest)
-> Lens
FollowTipRequest
FollowTipRequest
(Maybe FieldMask)
(Maybe FieldMask)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipRequest -> Maybe FieldMask
_FollowTipRequest'fieldMask
(\ FollowTipRequest
x__ Maybe FieldMask
y__ -> FollowTipRequest
x__ {_FollowTipRequest'fieldMask = y__}))
(FieldMask -> Lens' (Maybe FieldMask) FieldMask
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens FieldMask
forall msg. Message msg => msg
Data.ProtoLens.defMessage)
instance Data.ProtoLens.Field.HasField FollowTipRequest "maybe'fieldMask" (Prelude.Maybe Proto.Google.Protobuf.FieldMask.FieldMask) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'fieldMask"
-> (Maybe FieldMask -> f (Maybe FieldMask))
-> FollowTipRequest
-> f FollowTipRequest
fieldOf Proxy# "maybe'fieldMask"
_
= ((Maybe FieldMask -> f (Maybe FieldMask))
-> FollowTipRequest -> f FollowTipRequest)
-> ((Maybe FieldMask -> f (Maybe FieldMask))
-> Maybe FieldMask -> f (Maybe FieldMask))
-> (Maybe FieldMask -> f (Maybe FieldMask))
-> FollowTipRequest
-> f FollowTipRequest
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipRequest -> Maybe FieldMask)
-> (FollowTipRequest -> Maybe FieldMask -> FollowTipRequest)
-> Lens
FollowTipRequest
FollowTipRequest
(Maybe FieldMask)
(Maybe FieldMask)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipRequest -> Maybe FieldMask
_FollowTipRequest'fieldMask
(\ FollowTipRequest
x__ Maybe FieldMask
y__ -> FollowTipRequest
x__ {_FollowTipRequest'fieldMask = y__}))
(Maybe FieldMask -> f (Maybe FieldMask))
-> Maybe FieldMask -> f (Maybe FieldMask)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Message FollowTipRequest where
messageName :: Proxy FollowTipRequest -> Text
messageName Proxy FollowTipRequest
_
= String -> Text
Data.Text.pack String
"utxorpc.v1alpha.sync.FollowTipRequest"
packedMessageDescriptor :: Proxy FollowTipRequest -> ByteString
packedMessageDescriptor Proxy FollowTipRequest
_
= ByteString
"\n\
\\DLEFollowTipRequest\DC2<\n\
\\tintersect\CAN\SOH \ETX(\v2\RS.utxorpc.v1alpha.sync.BlockRefR\tintersect\DC29\n\
\\n\
\field_mask\CAN\STX \SOH(\v2\SUB.google.protobuf.FieldMaskR\tfieldMask"
packedFileDescriptor :: Proxy FollowTipRequest -> ByteString
packedFileDescriptor Proxy FollowTipRequest
_ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor FollowTipRequest)
fieldsByTag
= let
intersect__field_descriptor :: FieldDescriptor FollowTipRequest
intersect__field_descriptor
= String
-> FieldTypeDescriptor BlockRef
-> FieldAccessor FollowTipRequest BlockRef
-> FieldDescriptor FollowTipRequest
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"intersect"
(MessageOrGroup -> FieldTypeDescriptor BlockRef
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor BlockRef)
(Packing
-> Lens' FollowTipRequest [BlockRef]
-> FieldAccessor FollowTipRequest BlockRef
forall msg value.
Packing -> Lens' msg [value] -> FieldAccessor msg value
Data.ProtoLens.RepeatedField
Packing
Data.ProtoLens.Unpacked
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"intersect")) ::
Data.ProtoLens.FieldDescriptor FollowTipRequest
fieldMask__field_descriptor :: FieldDescriptor FollowTipRequest
fieldMask__field_descriptor
= String
-> FieldTypeDescriptor FieldMask
-> FieldAccessor FollowTipRequest FieldMask
-> FieldDescriptor FollowTipRequest
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"field_mask"
(MessageOrGroup -> FieldTypeDescriptor FieldMask
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor Proto.Google.Protobuf.FieldMask.FieldMask)
(Lens
FollowTipRequest
FollowTipRequest
(Maybe FieldMask)
(Maybe FieldMask)
-> FieldAccessor FollowTipRequest FieldMask
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'fieldMask")) ::
Data.ProtoLens.FieldDescriptor FollowTipRequest
in
[(Tag, FieldDescriptor FollowTipRequest)]
-> Map Tag (FieldDescriptor FollowTipRequest)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor FollowTipRequest
intersect__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor FollowTipRequest
fieldMask__field_descriptor)]
unknownFields :: Lens' FollowTipRequest FieldSet
unknownFields
= (FollowTipRequest -> FieldSet)
-> (FollowTipRequest -> FieldSet -> FollowTipRequest)
-> Lens' FollowTipRequest FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipRequest -> FieldSet
_FollowTipRequest'_unknownFields
(\ FollowTipRequest
x__ FieldSet
y__ -> FollowTipRequest
x__ {_FollowTipRequest'_unknownFields = y__})
defMessage :: FollowTipRequest
defMessage
= FollowTipRequest'_constructor
{_FollowTipRequest'intersect :: Vector BlockRef
_FollowTipRequest'intersect = Vector BlockRef
forall (v :: * -> *) a. Vector v a => v a
Data.Vector.Generic.empty,
_FollowTipRequest'fieldMask :: Maybe FieldMask
_FollowTipRequest'fieldMask = Maybe FieldMask
forall a. Maybe a
Prelude.Nothing,
_FollowTipRequest'_unknownFields :: FieldSet
_FollowTipRequest'_unknownFields = []}
parseMessage :: Parser FollowTipRequest
parseMessage
= let
loop ::
FollowTipRequest
-> Data.ProtoLens.Encoding.Growing.Growing Data.Vector.Vector Data.ProtoLens.Encoding.Growing.RealWorld BlockRef
-> Data.ProtoLens.Encoding.Bytes.Parser FollowTipRequest
loop :: FollowTipRequest
-> Growing Vector RealWorld BlockRef -> Parser FollowTipRequest
loop FollowTipRequest
x Growing Vector RealWorld BlockRef
mutable'intersect
= do Bool
end <- Parser Bool
Data.ProtoLens.Encoding.Bytes.atEnd
if Bool
end then
do Vector BlockRef
frozen'intersect <- IO (Vector BlockRef) -> Parser (Vector BlockRef)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) BlockRef -> IO (Vector BlockRef)
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 BlockRef
Growing Vector (PrimState IO) BlockRef
mutable'intersect)
(let missing :: [a]
missing = []
in
if [Any] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
String
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
FollowTipRequest -> Parser FollowTipRequest
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter FollowTipRequest FollowTipRequest FieldSet FieldSet
-> (FieldSet -> FieldSet) -> FollowTipRequest -> FollowTipRequest
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f FollowTipRequest FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FollowTipRequest FieldSet
Setter FollowTipRequest FollowTipRequest FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t)
(Setter
FollowTipRequest
FollowTipRequest
(Vector BlockRef)
(Vector BlockRef)
-> Vector BlockRef -> FollowTipRequest -> FollowTipRequest
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'intersect") Vector BlockRef
frozen'intersect FollowTipRequest
x))
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
Word64
10
-> do !BlockRef
y <- Parser BlockRef -> String -> Parser BlockRef
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser BlockRef -> Parser BlockRef
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 BlockRef
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"intersect"
Growing Vector RealWorld BlockRef
v <- IO (Growing Vector RealWorld BlockRef)
-> Parser (Growing Vector RealWorld BlockRef)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
(Growing Vector (PrimState IO) BlockRef
-> BlockRef -> IO (Growing Vector (PrimState IO) BlockRef)
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 BlockRef
Growing Vector (PrimState IO) BlockRef
mutable'intersect BlockRef
y)
FollowTipRequest
-> Growing Vector RealWorld BlockRef -> Parser FollowTipRequest
loop FollowTipRequest
x Growing Vector RealWorld BlockRef
v
Word64
18
-> do FieldMask
y <- Parser FieldMask -> String -> Parser FieldMask
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser FieldMask -> Parser FieldMask
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 FieldMask
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"field_mask"
FollowTipRequest
-> Growing Vector RealWorld BlockRef -> Parser FollowTipRequest
loop
(Setter FollowTipRequest FollowTipRequest FieldMask FieldMask
-> FieldMask -> FollowTipRequest -> FollowTipRequest
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"fieldMask") FieldMask
y FollowTipRequest
x)
Growing Vector RealWorld BlockRef
mutable'intersect
Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
FollowTipRequest
-> Growing Vector RealWorld BlockRef -> Parser FollowTipRequest
loop
(Setter FollowTipRequest FollowTipRequest FieldSet FieldSet
-> (FieldSet -> FieldSet) -> FollowTipRequest -> FollowTipRequest
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f FollowTipRequest FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FollowTipRequest FieldSet
Setter FollowTipRequest FollowTipRequest FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) FollowTipRequest
x)
Growing Vector RealWorld BlockRef
mutable'intersect
in
Parser FollowTipRequest -> String -> Parser FollowTipRequest
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Growing Vector RealWorld BlockRef
mutable'intersect <- IO (Growing Vector RealWorld BlockRef)
-> Parser (Growing Vector RealWorld BlockRef)
forall a. IO a -> Parser a
Data.ProtoLens.Encoding.Parser.Unsafe.unsafeLiftIO
IO (Growing Vector RealWorld BlockRef)
IO (Growing Vector (PrimState IO) BlockRef)
forall (m :: * -> *) (v :: * -> *) a.
(PrimMonad m, Vector v a) =>
m (Growing v (PrimState m) a)
Data.ProtoLens.Encoding.Growing.new
FollowTipRequest
-> Growing Vector RealWorld BlockRef -> Parser FollowTipRequest
loop FollowTipRequest
forall msg. Message msg => msg
Data.ProtoLens.defMessage Growing Vector RealWorld BlockRef
mutable'intersect)
String
"FollowTipRequest"
buildMessage :: FollowTipRequest -> Builder
buildMessage
= \ FollowTipRequest
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
((BlockRef -> Builder) -> Vector BlockRef -> Builder
forall (v :: * -> *) a.
Vector v a =>
(a -> Builder) -> v a -> Builder
Data.ProtoLens.Encoding.Bytes.foldMapBuilder
(\ BlockRef
_v
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
((ByteString -> Builder)
-> (BlockRef -> ByteString) -> BlockRef -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
BlockRef -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage BlockRef
_v))
(FoldLike
(Vector BlockRef)
FollowTipRequest
FollowTipRequest
(Vector BlockRef)
(Vector BlockRef)
-> FollowTipRequest -> Vector BlockRef
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"vec'intersect") FollowTipRequest
_x))
(Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe FieldMask)
FollowTipRequest
FollowTipRequest
(Maybe FieldMask)
(Maybe FieldMask)
-> FollowTipRequest -> Maybe FieldMask
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'fieldMask") FollowTipRequest
_x
of
Maybe FieldMask
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just FieldMask
_v)
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
((ByteString -> Builder)
-> (FieldMask -> ByteString) -> FieldMask -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
FieldMask -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage FieldMask
_v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet FollowTipRequest FollowTipRequest FieldSet FieldSet
-> FollowTipRequest -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet FollowTipRequest FollowTipRequest FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FollowTipRequest FieldSet
Data.ProtoLens.unknownFields FollowTipRequest
_x)))
instance Control.DeepSeq.NFData FollowTipRequest where
rnf :: FollowTipRequest -> ()
rnf
= \ FollowTipRequest
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(FollowTipRequest -> FieldSet
_FollowTipRequest'_unknownFields FollowTipRequest
x__)
(Vector BlockRef -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(FollowTipRequest -> Vector BlockRef
_FollowTipRequest'intersect FollowTipRequest
x__)
(Maybe FieldMask -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (FollowTipRequest -> Maybe FieldMask
_FollowTipRequest'fieldMask FollowTipRequest
x__) ()))
data FollowTipResponse
= FollowTipResponse'_constructor {FollowTipResponse -> Maybe FollowTipResponse'Action
_FollowTipResponse'action :: !(Prelude.Maybe FollowTipResponse'Action),
FollowTipResponse -> FieldSet
_FollowTipResponse'_unknownFields :: !Data.ProtoLens.FieldSet}
deriving stock (FollowTipResponse -> FollowTipResponse -> Bool
(FollowTipResponse -> FollowTipResponse -> Bool)
-> (FollowTipResponse -> FollowTipResponse -> Bool)
-> Eq FollowTipResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FollowTipResponse -> FollowTipResponse -> Bool
== :: FollowTipResponse -> FollowTipResponse -> Bool
$c/= :: FollowTipResponse -> FollowTipResponse -> Bool
/= :: FollowTipResponse -> FollowTipResponse -> Bool
Prelude.Eq, Eq FollowTipResponse
Eq FollowTipResponse =>
(FollowTipResponse -> FollowTipResponse -> Ordering)
-> (FollowTipResponse -> FollowTipResponse -> Bool)
-> (FollowTipResponse -> FollowTipResponse -> Bool)
-> (FollowTipResponse -> FollowTipResponse -> Bool)
-> (FollowTipResponse -> FollowTipResponse -> Bool)
-> (FollowTipResponse -> FollowTipResponse -> FollowTipResponse)
-> (FollowTipResponse -> FollowTipResponse -> FollowTipResponse)
-> Ord FollowTipResponse
FollowTipResponse -> FollowTipResponse -> Bool
FollowTipResponse -> FollowTipResponse -> Ordering
FollowTipResponse -> FollowTipResponse -> FollowTipResponse
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
$ccompare :: FollowTipResponse -> FollowTipResponse -> Ordering
compare :: FollowTipResponse -> FollowTipResponse -> Ordering
$c< :: FollowTipResponse -> FollowTipResponse -> Bool
< :: FollowTipResponse -> FollowTipResponse -> Bool
$c<= :: FollowTipResponse -> FollowTipResponse -> Bool
<= :: FollowTipResponse -> FollowTipResponse -> Bool
$c> :: FollowTipResponse -> FollowTipResponse -> Bool
> :: FollowTipResponse -> FollowTipResponse -> Bool
$c>= :: FollowTipResponse -> FollowTipResponse -> Bool
>= :: FollowTipResponse -> FollowTipResponse -> Bool
$cmax :: FollowTipResponse -> FollowTipResponse -> FollowTipResponse
max :: FollowTipResponse -> FollowTipResponse -> FollowTipResponse
$cmin :: FollowTipResponse -> FollowTipResponse -> FollowTipResponse
min :: FollowTipResponse -> FollowTipResponse -> FollowTipResponse
Prelude.Ord)
instance Prelude.Show FollowTipResponse where
showsPrec :: Int -> FollowTipResponse -> ShowS
showsPrec Int
_ FollowTipResponse
__x String
__s
= Char -> ShowS
Prelude.showChar
Char
'{'
(String -> ShowS
Prelude.showString
(FollowTipResponse -> String
forall msg. Message msg => msg -> String
Data.ProtoLens.showMessageShort FollowTipResponse
__x) (Char -> ShowS
Prelude.showChar Char
'}' String
__s))
data FollowTipResponse'Action
= FollowTipResponse'Apply !AnyChainBlock |
FollowTipResponse'Undo !AnyChainBlock |
FollowTipResponse'Reset !BlockRef
deriving stock (Int -> FollowTipResponse'Action -> ShowS
[FollowTipResponse'Action] -> ShowS
FollowTipResponse'Action -> String
(Int -> FollowTipResponse'Action -> ShowS)
-> (FollowTipResponse'Action -> String)
-> ([FollowTipResponse'Action] -> ShowS)
-> Show FollowTipResponse'Action
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FollowTipResponse'Action -> ShowS
showsPrec :: Int -> FollowTipResponse'Action -> ShowS
$cshow :: FollowTipResponse'Action -> String
show :: FollowTipResponse'Action -> String
$cshowList :: [FollowTipResponse'Action] -> ShowS
showList :: [FollowTipResponse'Action] -> ShowS
Prelude.Show, FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
(FollowTipResponse'Action -> FollowTipResponse'Action -> Bool)
-> (FollowTipResponse'Action -> FollowTipResponse'Action -> Bool)
-> Eq FollowTipResponse'Action
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
== :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
$c/= :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
/= :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
Prelude.Eq, Eq FollowTipResponse'Action
Eq FollowTipResponse'Action =>
(FollowTipResponse'Action -> FollowTipResponse'Action -> Ordering)
-> (FollowTipResponse'Action -> FollowTipResponse'Action -> Bool)
-> (FollowTipResponse'Action -> FollowTipResponse'Action -> Bool)
-> (FollowTipResponse'Action -> FollowTipResponse'Action -> Bool)
-> (FollowTipResponse'Action -> FollowTipResponse'Action -> Bool)
-> (FollowTipResponse'Action
-> FollowTipResponse'Action -> FollowTipResponse'Action)
-> (FollowTipResponse'Action
-> FollowTipResponse'Action -> FollowTipResponse'Action)
-> Ord FollowTipResponse'Action
FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
FollowTipResponse'Action -> FollowTipResponse'Action -> Ordering
FollowTipResponse'Action
-> FollowTipResponse'Action -> FollowTipResponse'Action
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
$ccompare :: FollowTipResponse'Action -> FollowTipResponse'Action -> Ordering
compare :: FollowTipResponse'Action -> FollowTipResponse'Action -> Ordering
$c< :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
< :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
$c<= :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
<= :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
$c> :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
> :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
$c>= :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
>= :: FollowTipResponse'Action -> FollowTipResponse'Action -> Bool
$cmax :: FollowTipResponse'Action
-> FollowTipResponse'Action -> FollowTipResponse'Action
max :: FollowTipResponse'Action
-> FollowTipResponse'Action -> FollowTipResponse'Action
$cmin :: FollowTipResponse'Action
-> FollowTipResponse'Action -> FollowTipResponse'Action
min :: FollowTipResponse'Action
-> FollowTipResponse'Action -> FollowTipResponse'Action
Prelude.Ord)
instance Data.ProtoLens.Field.HasField FollowTipResponse "maybe'action" (Prelude.Maybe FollowTipResponse'Action) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'action"
-> (Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> FollowTipResponse
-> f FollowTipResponse
fieldOf Proxy# "maybe'action"
_
= ((Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> FollowTipResponse -> f FollowTipResponse)
-> ((Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> (Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> FollowTipResponse
-> f FollowTipResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipResponse -> Maybe FollowTipResponse'Action)
-> (FollowTipResponse
-> Maybe FollowTipResponse'Action -> FollowTipResponse)
-> Lens
FollowTipResponse
FollowTipResponse
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipResponse -> Maybe FollowTipResponse'Action
_FollowTipResponse'action
(\ FollowTipResponse
x__ Maybe FollowTipResponse'Action
y__ -> FollowTipResponse
x__ {_FollowTipResponse'action = y__}))
(Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action)
forall a. a -> a
Prelude.id
instance Data.ProtoLens.Field.HasField FollowTipResponse "maybe'apply" (Prelude.Maybe AnyChainBlock) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'apply"
-> (Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> FollowTipResponse
-> f FollowTipResponse
fieldOf Proxy# "maybe'apply"
_
= ((Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> FollowTipResponse -> f FollowTipResponse)
-> ((Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> (Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> FollowTipResponse
-> f FollowTipResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipResponse -> Maybe FollowTipResponse'Action)
-> (FollowTipResponse
-> Maybe FollowTipResponse'Action -> FollowTipResponse)
-> Lens
FollowTipResponse
FollowTipResponse
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipResponse -> Maybe FollowTipResponse'Action
_FollowTipResponse'action
(\ FollowTipResponse
x__ Maybe FollowTipResponse'Action
y__ -> FollowTipResponse
x__ {_FollowTipResponse'action = y__}))
((Maybe FollowTipResponse'Action -> Maybe AnyChainBlock)
-> (Maybe FollowTipResponse'Action
-> Maybe AnyChainBlock -> Maybe FollowTipResponse'Action)
-> Lens
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
(Maybe AnyChainBlock)
(Maybe AnyChainBlock)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
(\ Maybe FollowTipResponse'Action
x__
-> case Maybe FollowTipResponse'Action
x__ of
(Prelude.Just (FollowTipResponse'Apply AnyChainBlock
x__val))
-> AnyChainBlock -> Maybe AnyChainBlock
forall a. a -> Maybe a
Prelude.Just AnyChainBlock
x__val
Maybe FollowTipResponse'Action
_otherwise -> Maybe AnyChainBlock
forall a. Maybe a
Prelude.Nothing)
(\ Maybe FollowTipResponse'Action
_ Maybe AnyChainBlock
y__ -> (AnyChainBlock -> FollowTipResponse'Action)
-> Maybe AnyChainBlock -> Maybe FollowTipResponse'Action
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap AnyChainBlock -> FollowTipResponse'Action
FollowTipResponse'Apply Maybe AnyChainBlock
y__))
instance Data.ProtoLens.Field.HasField FollowTipResponse "apply" AnyChainBlock where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "apply"
-> (AnyChainBlock -> f AnyChainBlock)
-> FollowTipResponse
-> f FollowTipResponse
fieldOf Proxy# "apply"
_
= ((Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> FollowTipResponse -> f FollowTipResponse)
-> ((AnyChainBlock -> f AnyChainBlock)
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> (AnyChainBlock -> f AnyChainBlock)
-> FollowTipResponse
-> f FollowTipResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipResponse -> Maybe FollowTipResponse'Action)
-> (FollowTipResponse
-> Maybe FollowTipResponse'Action -> FollowTipResponse)
-> Lens
FollowTipResponse
FollowTipResponse
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipResponse -> Maybe FollowTipResponse'Action
_FollowTipResponse'action
(\ FollowTipResponse
x__ Maybe FollowTipResponse'Action
y__ -> FollowTipResponse
x__ {_FollowTipResponse'action = y__}))
(((Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> ((AnyChainBlock -> f AnyChainBlock)
-> Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> (AnyChainBlock -> f AnyChainBlock)
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action)
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Maybe FollowTipResponse'Action -> Maybe AnyChainBlock)
-> (Maybe FollowTipResponse'Action
-> Maybe AnyChainBlock -> Maybe FollowTipResponse'Action)
-> Lens
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
(Maybe AnyChainBlock)
(Maybe AnyChainBlock)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
(\ Maybe FollowTipResponse'Action
x__
-> case Maybe FollowTipResponse'Action
x__ of
(Prelude.Just (FollowTipResponse'Apply AnyChainBlock
x__val))
-> AnyChainBlock -> Maybe AnyChainBlock
forall a. a -> Maybe a
Prelude.Just AnyChainBlock
x__val
Maybe FollowTipResponse'Action
_otherwise -> Maybe AnyChainBlock
forall a. Maybe a
Prelude.Nothing)
(\ Maybe FollowTipResponse'Action
_ Maybe AnyChainBlock
y__ -> (AnyChainBlock -> FollowTipResponse'Action)
-> Maybe AnyChainBlock -> Maybe FollowTipResponse'Action
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap AnyChainBlock -> FollowTipResponse'Action
FollowTipResponse'Apply Maybe AnyChainBlock
y__))
(AnyChainBlock -> Lens' (Maybe AnyChainBlock) AnyChainBlock
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens AnyChainBlock
forall msg. Message msg => msg
Data.ProtoLens.defMessage))
instance Data.ProtoLens.Field.HasField FollowTipResponse "maybe'undo" (Prelude.Maybe AnyChainBlock) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'undo"
-> (Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> FollowTipResponse
-> f FollowTipResponse
fieldOf Proxy# "maybe'undo"
_
= ((Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> FollowTipResponse -> f FollowTipResponse)
-> ((Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> (Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> FollowTipResponse
-> f FollowTipResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipResponse -> Maybe FollowTipResponse'Action)
-> (FollowTipResponse
-> Maybe FollowTipResponse'Action -> FollowTipResponse)
-> Lens
FollowTipResponse
FollowTipResponse
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipResponse -> Maybe FollowTipResponse'Action
_FollowTipResponse'action
(\ FollowTipResponse
x__ Maybe FollowTipResponse'Action
y__ -> FollowTipResponse
x__ {_FollowTipResponse'action = y__}))
((Maybe FollowTipResponse'Action -> Maybe AnyChainBlock)
-> (Maybe FollowTipResponse'Action
-> Maybe AnyChainBlock -> Maybe FollowTipResponse'Action)
-> Lens
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
(Maybe AnyChainBlock)
(Maybe AnyChainBlock)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
(\ Maybe FollowTipResponse'Action
x__
-> case Maybe FollowTipResponse'Action
x__ of
(Prelude.Just (FollowTipResponse'Undo AnyChainBlock
x__val))
-> AnyChainBlock -> Maybe AnyChainBlock
forall a. a -> Maybe a
Prelude.Just AnyChainBlock
x__val
Maybe FollowTipResponse'Action
_otherwise -> Maybe AnyChainBlock
forall a. Maybe a
Prelude.Nothing)
(\ Maybe FollowTipResponse'Action
_ Maybe AnyChainBlock
y__ -> (AnyChainBlock -> FollowTipResponse'Action)
-> Maybe AnyChainBlock -> Maybe FollowTipResponse'Action
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap AnyChainBlock -> FollowTipResponse'Action
FollowTipResponse'Undo Maybe AnyChainBlock
y__))
instance Data.ProtoLens.Field.HasField FollowTipResponse "undo" AnyChainBlock where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "undo"
-> (AnyChainBlock -> f AnyChainBlock)
-> FollowTipResponse
-> f FollowTipResponse
fieldOf Proxy# "undo"
_
= ((Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> FollowTipResponse -> f FollowTipResponse)
-> ((AnyChainBlock -> f AnyChainBlock)
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> (AnyChainBlock -> f AnyChainBlock)
-> FollowTipResponse
-> f FollowTipResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipResponse -> Maybe FollowTipResponse'Action)
-> (FollowTipResponse
-> Maybe FollowTipResponse'Action -> FollowTipResponse)
-> Lens
FollowTipResponse
FollowTipResponse
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipResponse -> Maybe FollowTipResponse'Action
_FollowTipResponse'action
(\ FollowTipResponse
x__ Maybe FollowTipResponse'Action
y__ -> FollowTipResponse
x__ {_FollowTipResponse'action = y__}))
(((Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> ((AnyChainBlock -> f AnyChainBlock)
-> Maybe AnyChainBlock -> f (Maybe AnyChainBlock))
-> (AnyChainBlock -> f AnyChainBlock)
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action)
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Maybe FollowTipResponse'Action -> Maybe AnyChainBlock)
-> (Maybe FollowTipResponse'Action
-> Maybe AnyChainBlock -> Maybe FollowTipResponse'Action)
-> Lens
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
(Maybe AnyChainBlock)
(Maybe AnyChainBlock)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
(\ Maybe FollowTipResponse'Action
x__
-> case Maybe FollowTipResponse'Action
x__ of
(Prelude.Just (FollowTipResponse'Undo AnyChainBlock
x__val))
-> AnyChainBlock -> Maybe AnyChainBlock
forall a. a -> Maybe a
Prelude.Just AnyChainBlock
x__val
Maybe FollowTipResponse'Action
_otherwise -> Maybe AnyChainBlock
forall a. Maybe a
Prelude.Nothing)
(\ Maybe FollowTipResponse'Action
_ Maybe AnyChainBlock
y__ -> (AnyChainBlock -> FollowTipResponse'Action)
-> Maybe AnyChainBlock -> Maybe FollowTipResponse'Action
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap AnyChainBlock -> FollowTipResponse'Action
FollowTipResponse'Undo Maybe AnyChainBlock
y__))
(AnyChainBlock -> Lens' (Maybe AnyChainBlock) AnyChainBlock
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens AnyChainBlock
forall msg. Message msg => msg
Data.ProtoLens.defMessage))
instance Data.ProtoLens.Field.HasField FollowTipResponse "maybe'reset" (Prelude.Maybe BlockRef) where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "maybe'reset"
-> (Maybe BlockRef -> f (Maybe BlockRef))
-> FollowTipResponse
-> f FollowTipResponse
fieldOf Proxy# "maybe'reset"
_
= ((Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> FollowTipResponse -> f FollowTipResponse)
-> ((Maybe BlockRef -> f (Maybe BlockRef))
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> (Maybe BlockRef -> f (Maybe BlockRef))
-> FollowTipResponse
-> f FollowTipResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipResponse -> Maybe FollowTipResponse'Action)
-> (FollowTipResponse
-> Maybe FollowTipResponse'Action -> FollowTipResponse)
-> Lens
FollowTipResponse
FollowTipResponse
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipResponse -> Maybe FollowTipResponse'Action
_FollowTipResponse'action
(\ FollowTipResponse
x__ Maybe FollowTipResponse'Action
y__ -> FollowTipResponse
x__ {_FollowTipResponse'action = y__}))
((Maybe FollowTipResponse'Action -> Maybe BlockRef)
-> (Maybe FollowTipResponse'Action
-> Maybe BlockRef -> Maybe FollowTipResponse'Action)
-> Lens
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
(Maybe BlockRef)
(Maybe BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
(\ Maybe FollowTipResponse'Action
x__
-> case Maybe FollowTipResponse'Action
x__ of
(Prelude.Just (FollowTipResponse'Reset BlockRef
x__val))
-> BlockRef -> Maybe BlockRef
forall a. a -> Maybe a
Prelude.Just BlockRef
x__val
Maybe FollowTipResponse'Action
_otherwise -> Maybe BlockRef
forall a. Maybe a
Prelude.Nothing)
(\ Maybe FollowTipResponse'Action
_ Maybe BlockRef
y__ -> (BlockRef -> FollowTipResponse'Action)
-> Maybe BlockRef -> Maybe FollowTipResponse'Action
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap BlockRef -> FollowTipResponse'Action
FollowTipResponse'Reset Maybe BlockRef
y__))
instance Data.ProtoLens.Field.HasField FollowTipResponse "reset" BlockRef where
fieldOf :: forall (f :: * -> *).
Functor f =>
Proxy# "reset"
-> (BlockRef -> f BlockRef)
-> FollowTipResponse
-> f FollowTipResponse
fieldOf Proxy# "reset"
_
= ((Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> FollowTipResponse -> f FollowTipResponse)
-> ((BlockRef -> f BlockRef)
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> (BlockRef -> f BlockRef)
-> FollowTipResponse
-> f FollowTipResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((FollowTipResponse -> Maybe FollowTipResponse'Action)
-> (FollowTipResponse
-> Maybe FollowTipResponse'Action -> FollowTipResponse)
-> Lens
FollowTipResponse
FollowTipResponse
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipResponse -> Maybe FollowTipResponse'Action
_FollowTipResponse'action
(\ FollowTipResponse
x__ Maybe FollowTipResponse'Action
y__ -> FollowTipResponse
x__ {_FollowTipResponse'action = y__}))
(((Maybe BlockRef -> f (Maybe BlockRef))
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action))
-> ((BlockRef -> f BlockRef)
-> Maybe BlockRef -> f (Maybe BlockRef))
-> (BlockRef -> f BlockRef)
-> Maybe FollowTipResponse'Action
-> f (Maybe FollowTipResponse'Action)
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
((Maybe FollowTipResponse'Action -> Maybe BlockRef)
-> (Maybe FollowTipResponse'Action
-> Maybe BlockRef -> Maybe FollowTipResponse'Action)
-> Lens
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
(Maybe BlockRef)
(Maybe BlockRef)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
(\ Maybe FollowTipResponse'Action
x__
-> case Maybe FollowTipResponse'Action
x__ of
(Prelude.Just (FollowTipResponse'Reset BlockRef
x__val))
-> BlockRef -> Maybe BlockRef
forall a. a -> Maybe a
Prelude.Just BlockRef
x__val
Maybe FollowTipResponse'Action
_otherwise -> Maybe BlockRef
forall a. Maybe a
Prelude.Nothing)
(\ Maybe FollowTipResponse'Action
_ Maybe BlockRef
y__ -> (BlockRef -> FollowTipResponse'Action)
-> Maybe BlockRef -> Maybe FollowTipResponse'Action
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.fmap BlockRef -> FollowTipResponse'Action
FollowTipResponse'Reset Maybe BlockRef
y__))
(BlockRef -> Lens' (Maybe BlockRef) BlockRef
forall b. b -> Lens' (Maybe b) b
Data.ProtoLens.maybeLens BlockRef
forall msg. Message msg => msg
Data.ProtoLens.defMessage))
instance Data.ProtoLens.Message FollowTipResponse where
messageName :: Proxy FollowTipResponse -> Text
messageName Proxy FollowTipResponse
_
= String -> Text
Data.Text.pack String
"utxorpc.v1alpha.sync.FollowTipResponse"
packedMessageDescriptor :: Proxy FollowTipResponse -> ByteString
packedMessageDescriptor Proxy FollowTipResponse
_
= ByteString
"\n\
\\DC1FollowTipResponse\DC2;\n\
\\ENQapply\CAN\SOH \SOH(\v2#.utxorpc.v1alpha.sync.AnyChainBlockH\NULR\ENQapply\DC29\n\
\\EOTundo\CAN\STX \SOH(\v2#.utxorpc.v1alpha.sync.AnyChainBlockH\NULR\EOTundo\DC26\n\
\\ENQreset\CAN\ETX \SOH(\v2\RS.utxorpc.v1alpha.sync.BlockRefH\NULR\ENQresetB\b\n\
\\ACKaction"
packedFileDescriptor :: Proxy FollowTipResponse -> ByteString
packedFileDescriptor Proxy FollowTipResponse
_ = ByteString
packedFileDescriptor
fieldsByTag :: Map Tag (FieldDescriptor FollowTipResponse)
fieldsByTag
= let
apply__field_descriptor :: FieldDescriptor FollowTipResponse
apply__field_descriptor
= String
-> FieldTypeDescriptor AnyChainBlock
-> FieldAccessor FollowTipResponse AnyChainBlock
-> FieldDescriptor FollowTipResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"apply"
(MessageOrGroup -> FieldTypeDescriptor AnyChainBlock
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor AnyChainBlock)
(Lens' FollowTipResponse (Maybe AnyChainBlock)
-> FieldAccessor FollowTipResponse AnyChainBlock
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'apply")) ::
Data.ProtoLens.FieldDescriptor FollowTipResponse
undo__field_descriptor :: FieldDescriptor FollowTipResponse
undo__field_descriptor
= String
-> FieldTypeDescriptor AnyChainBlock
-> FieldAccessor FollowTipResponse AnyChainBlock
-> FieldDescriptor FollowTipResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"undo"
(MessageOrGroup -> FieldTypeDescriptor AnyChainBlock
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor AnyChainBlock)
(Lens' FollowTipResponse (Maybe AnyChainBlock)
-> FieldAccessor FollowTipResponse AnyChainBlock
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'undo")) ::
Data.ProtoLens.FieldDescriptor FollowTipResponse
reset__field_descriptor :: FieldDescriptor FollowTipResponse
reset__field_descriptor
= String
-> FieldTypeDescriptor BlockRef
-> FieldAccessor FollowTipResponse BlockRef
-> FieldDescriptor FollowTipResponse
forall value msg.
String
-> FieldTypeDescriptor value
-> FieldAccessor msg value
-> FieldDescriptor msg
Data.ProtoLens.FieldDescriptor
String
"reset"
(MessageOrGroup -> FieldTypeDescriptor BlockRef
forall value.
Message value =>
MessageOrGroup -> FieldTypeDescriptor value
Data.ProtoLens.MessageField MessageOrGroup
Data.ProtoLens.MessageType ::
Data.ProtoLens.FieldTypeDescriptor BlockRef)
(Lens' FollowTipResponse (Maybe BlockRef)
-> FieldAccessor FollowTipResponse BlockRef
forall msg value.
Lens' msg (Maybe value) -> FieldAccessor msg value
Data.ProtoLens.OptionalField
(forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'reset")) ::
Data.ProtoLens.FieldDescriptor FollowTipResponse
in
[(Tag, FieldDescriptor FollowTipResponse)]
-> Map Tag (FieldDescriptor FollowTipResponse)
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList
[(Int -> Tag
Data.ProtoLens.Tag Int
1, FieldDescriptor FollowTipResponse
apply__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag Int
2, FieldDescriptor FollowTipResponse
undo__field_descriptor),
(Int -> Tag
Data.ProtoLens.Tag Int
3, FieldDescriptor FollowTipResponse
reset__field_descriptor)]
unknownFields :: Lens' FollowTipResponse FieldSet
unknownFields
= (FollowTipResponse -> FieldSet)
-> (FollowTipResponse -> FieldSet -> FollowTipResponse)
-> Lens' FollowTipResponse FieldSet
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.Family2.Unchecked.lens
FollowTipResponse -> FieldSet
_FollowTipResponse'_unknownFields
(\ FollowTipResponse
x__ FieldSet
y__ -> FollowTipResponse
x__ {_FollowTipResponse'_unknownFields = y__})
defMessage :: FollowTipResponse
defMessage
= FollowTipResponse'_constructor
{_FollowTipResponse'action :: Maybe FollowTipResponse'Action
_FollowTipResponse'action = Maybe FollowTipResponse'Action
forall a. Maybe a
Prelude.Nothing,
_FollowTipResponse'_unknownFields :: FieldSet
_FollowTipResponse'_unknownFields = []}
parseMessage :: Parser FollowTipResponse
parseMessage
= let
loop ::
FollowTipResponse
-> Data.ProtoLens.Encoding.Bytes.Parser FollowTipResponse
loop :: FollowTipResponse -> Parser FollowTipResponse
loop FollowTipResponse
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 a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
Prelude.null [Any]
forall a. [a]
missing then
() -> Parser ()
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return ()
else
String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail
(String -> ShowS
forall a. [a] -> [a] -> [a]
(Prelude.++)
String
"Missing required fields: "
([String] -> String
forall a. Show a => a -> String
Prelude.show ([String]
forall a. [a]
missing :: [Prelude.String]))))
FollowTipResponse -> Parser FollowTipResponse
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
Prelude.return
(Setter FollowTipResponse FollowTipResponse FieldSet FieldSet
-> (FieldSet -> FieldSet) -> FollowTipResponse -> FollowTipResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f FollowTipResponse FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FollowTipResponse FieldSet
Setter FollowTipResponse FollowTipResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> FieldSet -> FieldSet
forall a. [a] -> [a]
Prelude.reverse FieldSet
t) FollowTipResponse
x)
else
do Word64
tag <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
case Word64
tag of
Word64
10
-> do AnyChainBlock
y <- Parser AnyChainBlock -> String -> Parser AnyChainBlock
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser AnyChainBlock -> Parser AnyChainBlock
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 AnyChainBlock
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"apply"
FollowTipResponse -> Parser FollowTipResponse
loop (Setter
FollowTipResponse FollowTipResponse AnyChainBlock AnyChainBlock
-> AnyChainBlock -> FollowTipResponse -> FollowTipResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"apply") AnyChainBlock
y FollowTipResponse
x)
Word64
18
-> do AnyChainBlock
y <- Parser AnyChainBlock -> String -> Parser AnyChainBlock
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser AnyChainBlock -> Parser AnyChainBlock
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 AnyChainBlock
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"undo"
FollowTipResponse -> Parser FollowTipResponse
loop (Setter
FollowTipResponse FollowTipResponse AnyChainBlock AnyChainBlock
-> AnyChainBlock -> FollowTipResponse -> FollowTipResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"undo") AnyChainBlock
y FollowTipResponse
x)
Word64
26
-> do BlockRef
y <- Parser BlockRef -> String -> Parser BlockRef
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do Word64
len <- Parser Word64
Data.ProtoLens.Encoding.Bytes.getVarInt
Int -> Parser BlockRef -> Parser BlockRef
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 BlockRef
forall msg. Message msg => Parser msg
Data.ProtoLens.parseMessage)
String
"reset"
FollowTipResponse -> Parser FollowTipResponse
loop (Setter FollowTipResponse FollowTipResponse BlockRef BlockRef
-> BlockRef -> FollowTipResponse -> FollowTipResponse
forall s t a b. Setter s t a b -> b -> s -> t
Lens.Family2.set (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"reset") BlockRef
y FollowTipResponse
x)
Word64
wire
-> do !TaggedValue
y <- Word64 -> Parser TaggedValue
Data.ProtoLens.Encoding.Wire.parseTaggedValueFromWire
Word64
wire
FollowTipResponse -> Parser FollowTipResponse
loop
(Setter FollowTipResponse FollowTipResponse FieldSet FieldSet
-> (FieldSet -> FieldSet) -> FollowTipResponse -> FollowTipResponse
forall s t a b. Setter s t a b -> (a -> b) -> s -> t
Lens.Family2.over
LensLike' f FollowTipResponse FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FollowTipResponse FieldSet
Setter FollowTipResponse FollowTipResponse FieldSet FieldSet
Data.ProtoLens.unknownFields (\ !FieldSet
t -> (:) TaggedValue
y FieldSet
t) FollowTipResponse
x)
in
Parser FollowTipResponse -> String -> Parser FollowTipResponse
forall a. Parser a -> String -> Parser a
(Data.ProtoLens.Encoding.Bytes.<?>)
(do FollowTipResponse -> Parser FollowTipResponse
loop FollowTipResponse
forall msg. Message msg => msg
Data.ProtoLens.defMessage) String
"FollowTipResponse"
buildMessage :: FollowTipResponse -> Builder
buildMessage
= \ FollowTipResponse
_x
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(case
FoldLike
(Maybe FollowTipResponse'Action)
FollowTipResponse
FollowTipResponse
(Maybe FollowTipResponse'Action)
(Maybe FollowTipResponse'Action)
-> FollowTipResponse -> Maybe FollowTipResponse'Action
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view (forall (x :: Symbol) s a (f :: * -> *).
(HasField s x a, Functor f) =>
(a -> f a) -> s -> f s
Data.ProtoLens.Field.field @"maybe'action") FollowTipResponse
_x
of
Maybe FollowTipResponse'Action
Prelude.Nothing -> Builder
forall a. Monoid a => a
Data.Monoid.mempty
(Prelude.Just (FollowTipResponse'Apply AnyChainBlock
v))
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
10)
((ByteString -> Builder)
-> (AnyChainBlock -> ByteString) -> AnyChainBlock -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
AnyChainBlock -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage AnyChainBlock
v)
(Prelude.Just (FollowTipResponse'Undo AnyChainBlock
v))
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
18)
((ByteString -> Builder)
-> (AnyChainBlock -> ByteString) -> AnyChainBlock -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
AnyChainBlock -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage AnyChainBlock
v)
(Prelude.Just (FollowTipResponse'Reset BlockRef
v))
-> Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
(Data.Monoid.<>)
(Word64 -> Builder
Data.ProtoLens.Encoding.Bytes.putVarInt Word64
26)
((ByteString -> Builder)
-> (BlockRef -> ByteString) -> BlockRef -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
(Prelude..)
(\ 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))
BlockRef -> ByteString
forall msg. Message msg => msg -> ByteString
Data.ProtoLens.encodeMessage BlockRef
v))
(FieldSet -> Builder
Data.ProtoLens.Encoding.Wire.buildFieldSet
(FoldLike
FieldSet FollowTipResponse FollowTipResponse FieldSet FieldSet
-> FollowTipResponse -> FieldSet
forall a s t b. FoldLike a s t a b -> s -> a
Lens.Family2.view FoldLike
FieldSet FollowTipResponse FollowTipResponse FieldSet FieldSet
forall msg. Message msg => Lens' msg FieldSet
Lens' FollowTipResponse FieldSet
Data.ProtoLens.unknownFields FollowTipResponse
_x))
instance Control.DeepSeq.NFData FollowTipResponse where
rnf :: FollowTipResponse -> ()
rnf
= \ FollowTipResponse
x__
-> FieldSet -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq
(FollowTipResponse -> FieldSet
_FollowTipResponse'_unknownFields FollowTipResponse
x__)
(Maybe FollowTipResponse'Action -> () -> ()
forall a b. NFData a => a -> b -> b
Control.DeepSeq.deepseq (FollowTipResponse -> Maybe FollowTipResponse'Action
_FollowTipResponse'action FollowTipResponse
x__) ())
instance Control.DeepSeq.NFData FollowTipResponse'Action where
rnf :: FollowTipResponse'Action -> ()
rnf (FollowTipResponse'Apply AnyChainBlock
x__) = AnyChainBlock -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf AnyChainBlock
x__
rnf (FollowTipResponse'Undo AnyChainBlock
x__) = AnyChainBlock -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf AnyChainBlock
x__
rnf (FollowTipResponse'Reset BlockRef
x__) = BlockRef -> ()
forall a. NFData a => a -> ()
Control.DeepSeq.rnf BlockRef
x__
_FollowTipResponse'Apply ::
Data.ProtoLens.Prism.Prism' FollowTipResponse'Action AnyChainBlock
_FollowTipResponse'Apply :: Prism' FollowTipResponse'Action AnyChainBlock
_FollowTipResponse'Apply
= (AnyChainBlock -> FollowTipResponse'Action)
-> (FollowTipResponse'Action -> Maybe AnyChainBlock)
-> Prism' FollowTipResponse'Action AnyChainBlock
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
Data.ProtoLens.Prism.prism'
AnyChainBlock -> FollowTipResponse'Action
FollowTipResponse'Apply
(\ FollowTipResponse'Action
p__
-> case FollowTipResponse'Action
p__ of
(FollowTipResponse'Apply AnyChainBlock
p__val) -> AnyChainBlock -> Maybe AnyChainBlock
forall a. a -> Maybe a
Prelude.Just AnyChainBlock
p__val
FollowTipResponse'Action
_otherwise -> Maybe AnyChainBlock
forall a. Maybe a
Prelude.Nothing)
_FollowTipResponse'Undo ::
Data.ProtoLens.Prism.Prism' FollowTipResponse'Action AnyChainBlock
_FollowTipResponse'Undo :: Prism' FollowTipResponse'Action AnyChainBlock
_FollowTipResponse'Undo
= (AnyChainBlock -> FollowTipResponse'Action)
-> (FollowTipResponse'Action -> Maybe AnyChainBlock)
-> Prism' FollowTipResponse'Action AnyChainBlock
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
Data.ProtoLens.Prism.prism'
AnyChainBlock -> FollowTipResponse'Action
FollowTipResponse'Undo
(\ FollowTipResponse'Action
p__
-> case FollowTipResponse'Action
p__ of
(FollowTipResponse'Undo AnyChainBlock
p__val) -> AnyChainBlock -> Maybe AnyChainBlock
forall a. a -> Maybe a
Prelude.Just AnyChainBlock
p__val
FollowTipResponse'Action
_otherwise -> Maybe AnyChainBlock
forall a. Maybe a
Prelude.Nothing)
_FollowTipResponse'Reset ::
Data.ProtoLens.Prism.Prism' FollowTipResponse'Action BlockRef
_FollowTipResponse'Reset :: Prism' FollowTipResponse'Action BlockRef
_FollowTipResponse'Reset
= (BlockRef -> FollowTipResponse'Action)
-> (FollowTipResponse'Action -> Maybe BlockRef)
-> Prism' FollowTipResponse'Action BlockRef
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
Data.ProtoLens.Prism.prism'
BlockRef -> FollowTipResponse'Action
FollowTipResponse'Reset
(\ FollowTipResponse'Action
p__
-> case FollowTipResponse'Action
p__ of
(FollowTipResponse'Reset BlockRef
p__val) -> BlockRef -> Maybe BlockRef
forall a. a -> Maybe a
Prelude.Just BlockRef
p__val
FollowTipResponse'Action
_otherwise -> Maybe BlockRef
forall a. Maybe a
Prelude.Nothing)
data SyncService = SyncService {}
instance Data.ProtoLens.Service.Types.Service SyncService where
type ServiceName SyncService = "SyncService"
type ServicePackage SyncService = "utxorpc.v1alpha.sync"
type ServiceMethods SyncService = '["dumpHistory",
"fetchBlock",
"followTip"]
packedServiceDescriptor :: Proxy SyncService -> ByteString
packedServiceDescriptor Proxy SyncService
_
= ByteString
"\n\
\\vSyncService\DC2_\n\
\\n\
\FetchBlock\DC2'.utxorpc.v1alpha.sync.FetchBlockRequest\SUB(.utxorpc.v1alpha.sync.FetchBlockResponse\DC2b\n\
\\vDumpHistory\DC2(.utxorpc.v1alpha.sync.DumpHistoryRequest\SUB).utxorpc.v1alpha.sync.DumpHistoryResponse\DC2^\n\
\\tFollowTip\DC2&.utxorpc.v1alpha.sync.FollowTipRequest\SUB'.utxorpc.v1alpha.sync.FollowTipResponse0\SOH"
instance Data.ProtoLens.Service.Types.HasMethodImpl SyncService "fetchBlock" where
type MethodName SyncService "fetchBlock" = "FetchBlock"
type MethodInput SyncService "fetchBlock" = FetchBlockRequest
type MethodOutput SyncService "fetchBlock" = FetchBlockResponse
type MethodStreamingType SyncService "fetchBlock" = 'Data.ProtoLens.Service.Types.NonStreaming
instance Data.ProtoLens.Service.Types.HasMethodImpl SyncService "dumpHistory" where
type MethodName SyncService "dumpHistory" = "DumpHistory"
type MethodInput SyncService "dumpHistory" = DumpHistoryRequest
type MethodOutput SyncService "dumpHistory" = DumpHistoryResponse
type MethodStreamingType SyncService "dumpHistory" = 'Data.ProtoLens.Service.Types.NonStreaming
instance Data.ProtoLens.Service.Types.HasMethodImpl SyncService "followTip" where
type MethodName SyncService "followTip" = "FollowTip"
type MethodInput SyncService "followTip" = FollowTipRequest
type MethodOutput SyncService "followTip" = FollowTipResponse
type MethodStreamingType SyncService "followTip" = 'Data.ProtoLens.Service.Types.ServerStreaming
packedFileDescriptor :: Data.ByteString.ByteString
packedFileDescriptor :: ByteString
packedFileDescriptor
= ByteString
"\n\
\\USutxorpc/v1alpha/sync/sync.proto\DC2\DC4utxorpc.v1alpha.sync\SUB google/protobuf/field_mask.proto\SUB%utxorpc/v1alpha/cardano/cardano.proto\"4\n\
\\bBlockRef\DC2\DC4\n\
\\ENQindex\CAN\SOH \SOH(\EOTR\ENQindex\DC2\DC2\n\
\\EOThash\CAN\STX \SOH(\fR\EOThash\"w\n\
\\rAnyChainBlock\DC2!\n\
\\fnative_bytes\CAN\SOH \SOH(\fR\vnativeBytes\DC2:\n\
\\acardano\CAN\STX \SOH(\v2\RS.utxorpc.v1alpha.cardano.BlockH\NULR\acardanoB\a\n\
\\ENQchain\"\128\SOH\n\
\\DC1FetchBlockRequest\DC20\n\
\\ETXref\CAN\SOH \ETX(\v2\RS.utxorpc.v1alpha.sync.BlockRefR\ETXref\DC29\n\
\\n\
\field_mask\CAN\STX \SOH(\v2\SUB.google.protobuf.FieldMaskR\tfieldMask\"O\n\
\\DC2FetchBlockResponse\DC29\n\
\\ENQblock\CAN\SOH \ETX(\v2#.utxorpc.v1alpha.sync.AnyChainBlockR\ENQblock\"\173\SOH\n\
\\DC2DumpHistoryRequest\DC2?\n\
\\vstart_token\CAN\STX \SOH(\v2\RS.utxorpc.v1alpha.sync.BlockRefR\n\
\startToken\DC2\ESC\n\
\\tmax_items\CAN\ETX \SOH(\rR\bmaxItems\DC29\n\
\\n\
\field_mask\CAN\EOT \SOH(\v2\SUB.google.protobuf.FieldMaskR\tfieldMask\"\143\SOH\n\
\\DC3DumpHistoryResponse\DC29\n\
\\ENQblock\CAN\SOH \ETX(\v2#.utxorpc.v1alpha.sync.AnyChainBlockR\ENQblock\DC2=\n\
\\n\
\next_token\CAN\STX \SOH(\v2\RS.utxorpc.v1alpha.sync.BlockRefR\tnextToken\"\139\SOH\n\
\\DLEFollowTipRequest\DC2<\n\
\\tintersect\CAN\SOH \ETX(\v2\RS.utxorpc.v1alpha.sync.BlockRefR\tintersect\DC29\n\
\\n\
\field_mask\CAN\STX \SOH(\v2\SUB.google.protobuf.FieldMaskR\tfieldMask\"\205\SOH\n\
\\DC1FollowTipResponse\DC2;\n\
\\ENQapply\CAN\SOH \SOH(\v2#.utxorpc.v1alpha.sync.AnyChainBlockH\NULR\ENQapply\DC29\n\
\\EOTundo\CAN\STX \SOH(\v2#.utxorpc.v1alpha.sync.AnyChainBlockH\NULR\EOTundo\DC26\n\
\\ENQreset\CAN\ETX \SOH(\v2\RS.utxorpc.v1alpha.sync.BlockRefH\NULR\ENQresetB\b\n\
\\ACKaction2\178\STX\n\
\\vSyncService\DC2_\n\
\\n\
\FetchBlock\DC2'.utxorpc.v1alpha.sync.FetchBlockRequest\SUB(.utxorpc.v1alpha.sync.FetchBlockResponse\DC2b\n\
\\vDumpHistory\DC2(.utxorpc.v1alpha.sync.DumpHistoryRequest\SUB).utxorpc.v1alpha.sync.DumpHistoryResponse\DC2^\n\
\\tFollowTip\DC2&.utxorpc.v1alpha.sync.FollowTipRequest\SUB'.utxorpc.v1alpha.sync.FollowTipResponse0\SOHB\203\SOH\n\
\\CANcom.utxorpc.v1alpha.syncB\tSyncProtoP\SOHZ2github.com/utxorpc/go-codegen/utxorpc/v1alpha/sync\162\STX\ETXUVS\170\STX\DC4Utxorpc.V1alpha.Sync\202\STX\DC4Utxorpc\\V1alpha\\Sync\226\STX Utxorpc\\V1alpha\\Sync\\GPBMetadata\234\STX\SYNUtxorpc::V1alpha::SyncJ\170\DC4\n\
\\ACK\DC2\EOT\NUL\NUL@\SOH\n\
\\b\n\
\\SOH\f\DC2\ETX\NUL\NUL\DC2\n\
\\b\n\
\\SOH\STX\DC2\ETX\STX\NUL\GS\n\
\\t\n\
\\STX\ETX\NUL\DC2\ETX\EOT\NUL*\n\
\\t\n\
\\STX\ETX\SOH\DC2\ETX\ENQ\NUL/\n\
\8\n\
\\STX\EOT\NUL\DC2\EOT\b\NUL\v\SOH\SUB, Represents a reference to a specific block\n\
\\n\
\\n\
\\n\
\\ETX\EOT\NUL\SOH\DC2\ETX\b\b\DLE\n\
\B\n\
\\EOT\EOT\NUL\STX\NUL\DC2\ETX\t\STX\DC3\"5 Height or slot number (depending on the blockchain)\n\
\\n\
\\f\n\
\\ENQ\EOT\NUL\STX\NUL\ENQ\DC2\ETX\t\STX\b\n\
\\f\n\
\\ENQ\EOT\NUL\STX\NUL\SOH\DC2\ETX\t\t\SO\n\
\\f\n\
\\ENQ\EOT\NUL\STX\NUL\ETX\DC2\ETX\t\DC1\DC2\n\
\/\n\
\\EOT\EOT\NUL\STX\SOH\DC2\ETX\n\
\\STX\DC1\"\" Hash of the content of the block\n\
\\n\
\\f\n\
\\ENQ\EOT\NUL\STX\SOH\ENQ\DC2\ETX\n\
\\STX\a\n\
\\f\n\
\\ENQ\EOT\NUL\STX\SOH\SOH\DC2\ETX\n\
\\b\f\n\
\\f\n\
\\ENQ\EOT\NUL\STX\SOH\ETX\DC2\ETX\n\
\\SI\DLE\n\
\\n\
\\n\
\\STX\EOT\SOH\DC2\EOT\r\NUL\DC2\SOH\n\
\\n\
\\n\
\\ETX\EOT\SOH\SOH\DC2\ETX\r\b\NAK\n\
\5\n\
\\EOT\EOT\SOH\STX\NUL\DC2\ETX\SO\STX\EM\"( Original bytes as defined by the chain\n\
\\n\
\\f\n\
\\ENQ\EOT\SOH\STX\NUL\ENQ\DC2\ETX\SO\STX\a\n\
\\f\n\
\\ENQ\EOT\SOH\STX\NUL\SOH\DC2\ETX\SO\b\DC4\n\
\\f\n\
\\ENQ\EOT\SOH\STX\NUL\ETX\DC2\ETX\SO\ETB\CAN\n\
\\f\n\
\\EOT\EOT\SOH\b\NUL\DC2\EOT\SI\STX\DC1\ETX\n\
\\f\n\
\\ENQ\EOT\SOH\b\NUL\SOH\DC2\ETX\SI\b\r\n\
\&\n\
\\EOT\EOT\SOH\STX\SOH\DC2\ETX\DLE\EOT.\"\EM A parsed Cardano block.\n\
\\n\
\\f\n\
\\ENQ\EOT\SOH\STX\SOH\ACK\DC2\ETX\DLE\EOT!\n\
\\f\n\
\\ENQ\EOT\SOH\STX\SOH\SOH\DC2\ETX\DLE\")\n\
\\f\n\
\\ENQ\EOT\SOH\STX\SOH\ETX\DC2\ETX\DLE,-\n\
\8\n\
\\STX\EOT\STX\DC2\EOT\NAK\NUL\CAN\SOH\SUB, Request to fetch a block by its reference.\n\
\\n\
\\n\
\\n\
\\ETX\EOT\STX\SOH\DC2\ETX\NAK\b\EM\n\
\(\n\
\\EOT\EOT\STX\STX\NUL\DC2\ETX\SYN\STX\FS\"\ESC List of block references.\n\
\\n\
\\f\n\
\\ENQ\EOT\STX\STX\NUL\EOT\DC2\ETX\SYN\STX\n\
\\n\
\\f\n\
\\ENQ\EOT\STX\STX\NUL\ACK\DC2\ETX\SYN\v\DC3\n\
\\f\n\
\\ENQ\EOT\STX\STX\NUL\SOH\DC2\ETX\SYN\DC4\ETB\n\
\\f\n\
\\ENQ\EOT\STX\STX\NUL\ETX\DC2\ETX\SYN\SUB\ESC\n\
\7\n\
\\EOT\EOT\STX\STX\SOH\DC2\ETX\ETB\STX+\"* Field mask to selectively return fields.\n\
\\n\
\\f\n\
\\ENQ\EOT\STX\STX\SOH\ACK\DC2\ETX\ETB\STX\ESC\n\
\\f\n\
\\ENQ\EOT\STX\STX\SOH\SOH\DC2\ETX\ETB\FS&\n\
\\f\n\
\\ENQ\EOT\STX\STX\SOH\ETX\DC2\ETX\ETB)*\n\
\5\n\
\\STX\EOT\ETX\DC2\EOT\ESC\NUL\GS\SOH\SUB) Response containing the fetched blocks.\n\
\\n\
\\n\
\\n\
\\ETX\EOT\ETX\SOH\DC2\ETX\ESC\b\SUB\n\
\&\n\
\\EOT\EOT\ETX\STX\NUL\DC2\ETX\FS\STX#\"\EM List of fetched blocks.\n\
\\n\
\\f\n\
\\ENQ\EOT\ETX\STX\NUL\EOT\DC2\ETX\FS\STX\n\
\\n\
\\f\n\
\\ENQ\EOT\ETX\STX\NUL\ACK\DC2\ETX\FS\v\CAN\n\
\\f\n\
\\ENQ\EOT\ETX\STX\NUL\SOH\DC2\ETX\FS\EM\RS\n\
\\f\n\
\\ENQ\EOT\ETX\STX\NUL\ETX\DC2\ETX\FS!\"\n\
\0\n\
\\STX\EOT\EOT\DC2\EOT \NUL$\SOH\SUB$ Request to dump the block history.\n\
\\n\
\\n\
\\n\
\\ETX\EOT\EOT\SOH\DC2\ETX \b\SUB\n\
\9\n\
\\EOT\EOT\EOT\STX\NUL\DC2\ETX!\STX\ESC\", Starting point for the block history dump.\n\
\\n\
\\f\n\
\\ENQ\EOT\EOT\STX\NUL\ACK\DC2\ETX!\STX\n\
\\n\
\\f\n\
\\ENQ\EOT\EOT\STX\NUL\SOH\DC2\ETX!\v\SYN\n\
\\f\n\
\\ENQ\EOT\EOT\STX\NUL\ETX\DC2\ETX!\EM\SUB\n\
\1\n\
\\EOT\EOT\EOT\STX\SOH\DC2\ETX\"\STX\ETB\"$ Maximum number of items to return.\n\
\\n\
\\f\n\
\\ENQ\EOT\EOT\STX\SOH\ENQ\DC2\ETX\"\STX\b\n\
\\f\n\
\\ENQ\EOT\EOT\STX\SOH\SOH\DC2\ETX\"\t\DC2\n\
\\f\n\
\\ENQ\EOT\EOT\STX\SOH\ETX\DC2\ETX\"\NAK\SYN\n\
\7\n\
\\EOT\EOT\EOT\STX\STX\DC2\ETX#\STX+\"* Field mask to selectively return fields.\n\
\\n\
\\f\n\
\\ENQ\EOT\EOT\STX\STX\ACK\DC2\ETX#\STX\ESC\n\
\\f\n\
\\ENQ\EOT\EOT\STX\STX\SOH\DC2\ETX#\FS&\n\
\\f\n\
\\ENQ\EOT\EOT\STX\STX\ETX\DC2\ETX#)*\n\
\;\n\
\\STX\EOT\ENQ\DC2\EOT'\NUL*\SOH\SUB/ Response containing the dumped block history.\n\
\\n\
\\n\
\\n\
\\ETX\EOT\ENQ\SOH\DC2\ETX'\b\ESC\n\
\-\n\
\\EOT\EOT\ENQ\STX\NUL\DC2\ETX(\STX#\" List of blocks in the history.\n\
\\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\NUL\EOT\DC2\ETX(\STX\n\
\\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\NUL\ACK\DC2\ETX(\v\CAN\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\NUL\SOH\DC2\ETX(\EM\RS\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\NUL\ETX\DC2\ETX(!\"\n\
\)\n\
\\EOT\EOT\ENQ\STX\SOH\DC2\ETX)\STX\SUB\"\FS Next token for pagination.\n\
\\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\SOH\ACK\DC2\ETX)\STX\n\
\\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\SOH\SOH\DC2\ETX)\v\NAK\n\
\\f\n\
\\ENQ\EOT\ENQ\STX\SOH\ETX\DC2\ETX)\CAN\EM\n\
\:\n\
\\STX\EOT\ACK\DC2\EOT-\NUL0\SOH\SUB. Request to follow the tip of the blockchain.\n\
\\n\
\\n\
\\n\
\\ETX\EOT\ACK\SOH\DC2\ETX-\b\CAN\n\
\A\n\
\\EOT\EOT\ACK\STX\NUL\DC2\ETX.\STX\"\"4 List of block references to find the intersection.\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\NUL\EOT\DC2\ETX.\STX\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\NUL\ACK\DC2\ETX.\v\DC3\n\
\\f\n\
\\ENQ\EOT\ACK\STX\NUL\SOH\DC2\ETX.\DC4\GS\n\
\\f\n\
\\ENQ\EOT\ACK\STX\NUL\ETX\DC2\ETX. !\n\
\7\n\
\\EOT\EOT\ACK\STX\SOH\DC2\ETX/\STX+\"* Field mask to selectively return fields.\n\
\\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SOH\ACK\DC2\ETX/\STX\ESC\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SOH\SOH\DC2\ETX/\FS&\n\
\\f\n\
\\ENQ\EOT\ACK\STX\SOH\ETX\DC2\ETX/)*\n\
\P\n\
\\STX\EOT\a\DC2\EOT3\NUL9\SOH\SUBD Response containing the action to perform while following the tip.\n\
\\n\
\\n\
\\n\
\\ETX\EOT\a\SOH\DC2\ETX3\b\EM\n\
\\f\n\
\\EOT\EOT\a\b\NUL\DC2\EOT4\STX8\ETX\n\
\\f\n\
\\ENQ\EOT\a\b\NUL\SOH\DC2\ETX4\b\SO\n\
\ \n\
\\EOT\EOT\a\STX\NUL\DC2\ETX5\EOT\FS\"\DC3 Apply this block.\n\
\\n\
\\f\n\
\\ENQ\EOT\a\STX\NUL\ACK\DC2\ETX5\EOT\DC1\n\
\\f\n\
\\ENQ\EOT\a\STX\NUL\SOH\DC2\ETX5\DC2\ETB\n\
\\f\n\
\\ENQ\EOT\a\STX\NUL\ETX\DC2\ETX5\SUB\ESC\n\
\\US\n\
\\EOT\EOT\a\STX\SOH\DC2\ETX6\EOT\ESC\"\DC2 Undo this block.\n\
\\n\
\\f\n\
\\ENQ\EOT\a\STX\SOH\ACK\DC2\ETX6\EOT\DC1\n\
\\f\n\
\\ENQ\EOT\a\STX\SOH\SOH\DC2\ETX6\DC2\SYN\n\
\\f\n\
\\ENQ\EOT\a\STX\SOH\ETX\DC2\ETX6\EM\SUB\n\
\-\n\
\\EOT\EOT\a\STX\STX\DC2\ETX7\EOT\ETB\" Reset to this block reference.\n\
\\n\
\\f\n\
\\ENQ\EOT\a\STX\STX\ACK\DC2\ETX7\EOT\f\n\
\\f\n\
\\ENQ\EOT\a\STX\STX\SOH\DC2\ETX7\r\DC2\n\
\\f\n\
\\ENQ\EOT\a\STX\STX\ETX\DC2\ETX7\NAK\SYN\n\
\8\n\
\\STX\ACK\NUL\DC2\EOT<\NUL@\SOH\SUB, Service definition for syncing chain data.\n\
\\n\
\\n\
\\n\
\\ETX\ACK\NUL\SOH\DC2\ETX<\b\DC3\n\
\.\n\
\\EOT\ACK\NUL\STX\NUL\DC2\ETX=\STXA\"! Fetch a block by its reference.\n\
\\n\
\\f\n\
\\ENQ\ACK\NUL\STX\NUL\SOH\DC2\ETX=\ACK\DLE\n\
\\f\n\
\\ENQ\ACK\NUL\STX\NUL\STX\DC2\ETX=\DC1\"\n\
\\f\n\
\\ENQ\ACK\NUL\STX\NUL\ETX\DC2\ETX=-?\n\
\&\n\
\\EOT\ACK\NUL\STX\SOH\DC2\ETX>\STXD\"\EM Dump the block history.\n\
\\n\
\\f\n\
\\ENQ\ACK\NUL\STX\SOH\SOH\DC2\ETX>\ACK\DC1\n\
\\f\n\
\\ENQ\ACK\NUL\STX\SOH\STX\DC2\ETX>\DC2$\n\
\\f\n\
\\ENQ\ACK\NUL\STX\SOH\ETX\DC2\ETX>/B\n\
\0\n\
\\EOT\ACK\NUL\STX\STX\DC2\ETX?\STXE\"# Follow the tip of the blockchain.\n\
\\n\
\\f\n\
\\ENQ\ACK\NUL\STX\STX\SOH\DC2\ETX?\ACK\SI\n\
\\f\n\
\\ENQ\ACK\NUL\STX\STX\STX\DC2\ETX?\DLE \n\
\\f\n\
\\ENQ\ACK\NUL\STX\STX\ACK\DC2\ETX?+1\n\
\\f\n\
\\ENQ\ACK\NUL\STX\STX\ETX\DC2\ETX?2Cb\ACKproto3"