{-# LANGUAGE TemplateHaskell #-}
module Network.ABCI.Types.Messages.Request where
import Control.Lens (iso, (&), (.~), (^.),
(^..), (^?), _Just)
import Control.Lens.Wrapped (Wrapped (..),
_Unwrapped')
import Data.Aeson (FromJSON (..),
ToJSON (..),
genericParseJSON,
genericToJSON,
withObject, (.!=),
(.:), (.:?))
import Data.ByteArray.Base64String (Base64String)
import qualified Data.ByteArray.Base64String as Base64
import Data.ByteArray.HexString (HexString)
import qualified Data.ByteArray.HexString as Hex
import Data.Default.Class (Default (..))
import Data.Int (Int64)
import Data.ProtoLens.Message (Message (defMessage))
import Data.Text (Text)
import Data.Word (Word64)
import GHC.Generics (Generic)
import Network.ABCI.Types.Messages.Common (defaultABCIOptions,
makeABCILenses)
import Network.ABCI.Types.Messages.FieldTypes (ConsensusParams (..),
Evidence (..),
Header (..),
LastCommitInfo (..),
Timestamp (..),
ValidatorUpdate (..),
WrappedVal (..))
import qualified Proto.Types as PT
import qualified Proto.Types_Fields as PT
data Echo = Echo
{ Echo -> Text
echoMessage :: Text
} deriving (Echo -> Echo -> Bool
(Echo -> Echo -> Bool) -> (Echo -> Echo -> Bool) -> Eq Echo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Echo -> Echo -> Bool
$c/= :: Echo -> Echo -> Bool
== :: Echo -> Echo -> Bool
$c== :: Echo -> Echo -> Bool
Eq, Int -> Echo -> ShowS
[Echo] -> ShowS
Echo -> String
(Int -> Echo -> ShowS)
-> (Echo -> String) -> ([Echo] -> ShowS) -> Show Echo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Echo] -> ShowS
$cshowList :: [Echo] -> ShowS
show :: Echo -> String
$cshow :: Echo -> String
showsPrec :: Int -> Echo -> ShowS
$cshowsPrec :: Int -> Echo -> ShowS
Show, (forall x. Echo -> Rep Echo x)
-> (forall x. Rep Echo x -> Echo) -> Generic Echo
forall x. Rep Echo x -> Echo
forall x. Echo -> Rep Echo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Echo x -> Echo
$cfrom :: forall x. Echo -> Rep Echo x
Generic)
makeABCILenses ''Echo
instance ToJSON Echo where
toJSON :: Echo -> Value
toJSON = Options -> Echo -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Echo -> Value) -> Options -> Echo -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "echo"
instance FromJSON Echo where
parseJSON :: Value -> Parser Echo
parseJSON = Options -> Value -> Parser Echo
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Echo)
-> Options -> Value -> Parser Echo
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "echo"
instance Wrapped Echo where
type Unwrapped Echo = PT.RequestEcho
_Wrapped' :: p (Unwrapped Echo) (f (Unwrapped Echo)) -> p Echo (f Echo)
_Wrapped' = (Echo -> RequestEcho)
-> (RequestEcho -> Echo) -> Iso Echo Echo RequestEcho RequestEcho
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Echo -> RequestEcho
forall b. (Message b, HasField b "message" Text) => Echo -> b
t RequestEcho -> Echo
forall s. HasField s "message" Text => s -> Echo
f
where
t :: Echo -> b
t Echo {..} = b
forall msg. Message msg => msg
defMessage b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Text
forall (f :: * -> *) s a.
(Functor f, HasField s "message" a) =>
LensLike' f s a
PT.message LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
echoMessage
f :: s -> Echo
f message :: s
message = Echo :: Text -> Echo
Echo { echoMessage :: Text
echoMessage = s
message s -> Getting Text s Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text s Text
forall (f :: * -> *) s a.
(Functor f, HasField s "message" a) =>
LensLike' f s a
PT.message }
instance Default Echo where
def :: Echo
def = RequestEcho
forall msg. Message msg => msg
defMessage RequestEcho -> Getting Echo RequestEcho Echo -> Echo
forall s a. s -> Getting a s a -> a
^. Getting Echo RequestEcho Echo
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data Flush =
Flush deriving (Flush -> Flush -> Bool
(Flush -> Flush -> Bool) -> (Flush -> Flush -> Bool) -> Eq Flush
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Flush -> Flush -> Bool
$c/= :: Flush -> Flush -> Bool
== :: Flush -> Flush -> Bool
$c== :: Flush -> Flush -> Bool
Eq, Int -> Flush -> ShowS
[Flush] -> ShowS
Flush -> String
(Int -> Flush -> ShowS)
-> (Flush -> String) -> ([Flush] -> ShowS) -> Show Flush
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Flush] -> ShowS
$cshowList :: [Flush] -> ShowS
show :: Flush -> String
$cshow :: Flush -> String
showsPrec :: Int -> Flush -> ShowS
$cshowsPrec :: Int -> Flush -> ShowS
Show, (forall x. Flush -> Rep Flush x)
-> (forall x. Rep Flush x -> Flush) -> Generic Flush
forall x. Rep Flush x -> Flush
forall x. Flush -> Rep Flush x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Flush x -> Flush
$cfrom :: forall x. Flush -> Rep Flush x
Generic)
instance ToJSON Flush where
toJSON :: Flush -> Value
toJSON = Options -> Flush -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Flush -> Value) -> Options -> Flush -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "flush"
instance FromJSON Flush where
parseJSON :: Value -> Parser Flush
parseJSON = Options -> Value -> Parser Flush
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Flush)
-> Options -> Value -> Parser Flush
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "flush"
instance Wrapped Flush where
type Unwrapped Flush = PT.RequestFlush
_Wrapped' :: p (Unwrapped Flush) (f (Unwrapped Flush)) -> p Flush (f Flush)
_Wrapped' = (Flush -> RequestFlush)
-> (RequestFlush -> Flush)
-> Iso Flush Flush RequestFlush RequestFlush
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Flush -> RequestFlush
forall b. b -> RequestFlush
t RequestFlush -> Flush
forall b. b -> Flush
f
where
t :: b -> RequestFlush
t = RequestFlush -> b -> RequestFlush
forall a b. a -> b -> a
const RequestFlush
forall msg. Message msg => msg
defMessage
f :: b -> Flush
f = Flush -> b -> Flush
forall a b. a -> b -> a
const Flush
Flush
instance Default Flush where
def :: Flush
def = RequestFlush
forall msg. Message msg => msg
defMessage RequestFlush -> Getting Flush RequestFlush Flush -> Flush
forall s a. s -> Getting a s a -> a
^. Getting Flush RequestFlush Flush
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data Info = Info
{ Info -> Text
infoVersion :: Text
, Info -> Word64
infoBlockVersion :: Word64
, Info -> Word64
infoP2pVersion :: Word64
} deriving (Info -> Info -> Bool
(Info -> Info -> Bool) -> (Info -> Info -> Bool) -> Eq Info
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Info -> Info -> Bool
$c/= :: Info -> Info -> Bool
== :: Info -> Info -> Bool
$c== :: Info -> Info -> Bool
Eq, Int -> Info -> ShowS
[Info] -> ShowS
Info -> String
(Int -> Info -> ShowS)
-> (Info -> String) -> ([Info] -> ShowS) -> Show Info
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Info] -> ShowS
$cshowList :: [Info] -> ShowS
show :: Info -> String
$cshow :: Info -> String
showsPrec :: Int -> Info -> ShowS
$cshowsPrec :: Int -> Info -> ShowS
Show, (forall x. Info -> Rep Info x)
-> (forall x. Rep Info x -> Info) -> Generic Info
forall x. Rep Info x -> Info
forall x. Info -> Rep Info x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Info x -> Info
$cfrom :: forall x. Info -> Rep Info x
Generic)
makeABCILenses ''Info
instance ToJSON Info where
toJSON :: Info -> Value
toJSON = Options -> Info -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Info -> Value) -> Options -> Info -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "info"
instance FromJSON Info where
parseJSON :: Value -> Parser Info
parseJSON = Options -> Value -> Parser Info
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Info)
-> Options -> Value -> Parser Info
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "info"
instance Wrapped Info where
type Unwrapped Info = PT.RequestInfo
_Wrapped' :: p (Unwrapped Info) (f (Unwrapped Info)) -> p Info (f Info)
_Wrapped' = (Info -> RequestInfo)
-> (RequestInfo -> Info) -> Iso Info Info RequestInfo RequestInfo
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Info -> RequestInfo
forall b.
(Message b, HasField b "blockVersion" Word64,
HasField b "p2pVersion" Word64, HasField b "version" Text) =>
Info -> b
t RequestInfo -> Info
forall s.
(HasField s "blockVersion" Word64, HasField s "p2pVersion" Word64,
HasField s "version" Text) =>
s -> Info
f
where
t :: Info -> b
t Info {..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Text
forall (f :: * -> *) s a.
(Functor f, HasField s "version" a) =>
LensLike' f s a
PT.version LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
infoVersion
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "blockVersion" a) =>
LensLike' f s a
PT.blockVersion LensLike' Identity b Word64 -> Word64 -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
infoBlockVersion
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "p2pVersion" a) =>
LensLike' f s a
PT.p2pVersion LensLike' Identity b Word64 -> Word64 -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Word64
infoP2pVersion
f :: s -> Info
f message :: s
message = Info :: Text -> Word64 -> Word64 -> Info
Info { infoVersion :: Text
infoVersion = s
message s -> Getting Text s Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text s Text
forall (f :: * -> *) s a.
(Functor f, HasField s "version" a) =>
LensLike' f s a
PT.version
, infoBlockVersion :: Word64
infoBlockVersion = s
message s -> Getting Word64 s Word64 -> Word64
forall s a. s -> Getting a s a -> a
^. Getting Word64 s Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "blockVersion" a) =>
LensLike' f s a
PT.blockVersion
, infoP2pVersion :: Word64
infoP2pVersion = s
message s -> Getting Word64 s Word64 -> Word64
forall s a. s -> Getting a s a -> a
^. Getting Word64 s Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "p2pVersion" a) =>
LensLike' f s a
PT.p2pVersion
}
instance Default Info where
def :: Info
def = RequestInfo
forall msg. Message msg => msg
defMessage RequestInfo -> Getting Info RequestInfo Info -> Info
forall s a. s -> Getting a s a -> a
^. Getting Info RequestInfo Info
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data SetOption = SetOption
{ SetOption -> Text
setOptionKey :: Text
, SetOption -> Text
setOptionValue :: Text
} deriving (SetOption -> SetOption -> Bool
(SetOption -> SetOption -> Bool)
-> (SetOption -> SetOption -> Bool) -> Eq SetOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetOption -> SetOption -> Bool
$c/= :: SetOption -> SetOption -> Bool
== :: SetOption -> SetOption -> Bool
$c== :: SetOption -> SetOption -> Bool
Eq, Int -> SetOption -> ShowS
[SetOption] -> ShowS
SetOption -> String
(Int -> SetOption -> ShowS)
-> (SetOption -> String)
-> ([SetOption] -> ShowS)
-> Show SetOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetOption] -> ShowS
$cshowList :: [SetOption] -> ShowS
show :: SetOption -> String
$cshow :: SetOption -> String
showsPrec :: Int -> SetOption -> ShowS
$cshowsPrec :: Int -> SetOption -> ShowS
Show, (forall x. SetOption -> Rep SetOption x)
-> (forall x. Rep SetOption x -> SetOption) -> Generic SetOption
forall x. Rep SetOption x -> SetOption
forall x. SetOption -> Rep SetOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetOption x -> SetOption
$cfrom :: forall x. SetOption -> Rep SetOption x
Generic)
makeABCILenses ''SetOption
instance ToJSON SetOption where
toJSON :: SetOption -> Value
toJSON = Options -> SetOption -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> SetOption -> Value) -> Options -> SetOption -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "setOption"
instance FromJSON SetOption where
parseJSON :: Value -> Parser SetOption
parseJSON = Options -> Value -> Parser SetOption
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser SetOption)
-> Options -> Value -> Parser SetOption
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "setOption"
instance Wrapped SetOption where
type Unwrapped SetOption = PT.RequestSetOption
_Wrapped' :: p (Unwrapped SetOption) (f (Unwrapped SetOption))
-> p SetOption (f SetOption)
_Wrapped' = (SetOption -> RequestSetOption)
-> (RequestSetOption -> SetOption)
-> Iso SetOption SetOption RequestSetOption RequestSetOption
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso SetOption -> RequestSetOption
forall b.
(Message b, HasField b "key" Text, HasField b "value" Text) =>
SetOption -> b
t RequestSetOption -> SetOption
forall s.
(HasField s "key" Text, HasField s "value" Text) =>
s -> SetOption
f
where
t :: SetOption -> b
t SetOption {..} =
b
forall msg. Message msg => msg
defMessage b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Text
forall (f :: * -> *) s a.
(Functor f, HasField s "key" a) =>
LensLike' f s a
PT.key LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
setOptionKey b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Text
forall (f :: * -> *) s a.
(Functor f, HasField s "value" a) =>
LensLike' f s a
PT.value LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
setOptionValue
f :: s -> SetOption
f message :: s
message = SetOption :: Text -> Text -> SetOption
SetOption { setOptionKey :: Text
setOptionKey = s
message s -> Getting Text s Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text s Text
forall (f :: * -> *) s a.
(Functor f, HasField s "key" a) =>
LensLike' f s a
PT.key
, setOptionValue :: Text
setOptionValue = s
message s -> Getting Text s Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text s Text
forall (f :: * -> *) s a.
(Functor f, HasField s "value" a) =>
LensLike' f s a
PT.value
}
instance Default SetOption where
def :: SetOption
def = RequestSetOption
forall msg. Message msg => msg
defMessage RequestSetOption
-> Getting SetOption RequestSetOption SetOption -> SetOption
forall s a. s -> Getting a s a -> a
^. Getting SetOption RequestSetOption SetOption
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data InitChain = InitChain
{ InitChain -> Maybe Timestamp
initChainTime :: Maybe Timestamp
, InitChain -> Text
initChainChainId :: Text
, InitChain -> Maybe ConsensusParams
initChainConsensusParams :: Maybe ConsensusParams
, InitChain -> [ValidatorUpdate]
initChainValidators :: [ValidatorUpdate]
, InitChain -> Base64String
initChainAppState :: Base64String
} deriving (InitChain -> InitChain -> Bool
(InitChain -> InitChain -> Bool)
-> (InitChain -> InitChain -> Bool) -> Eq InitChain
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InitChain -> InitChain -> Bool
$c/= :: InitChain -> InitChain -> Bool
== :: InitChain -> InitChain -> Bool
$c== :: InitChain -> InitChain -> Bool
Eq, Int -> InitChain -> ShowS
[InitChain] -> ShowS
InitChain -> String
(Int -> InitChain -> ShowS)
-> (InitChain -> String)
-> ([InitChain] -> ShowS)
-> Show InitChain
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InitChain] -> ShowS
$cshowList :: [InitChain] -> ShowS
show :: InitChain -> String
$cshow :: InitChain -> String
showsPrec :: Int -> InitChain -> ShowS
$cshowsPrec :: Int -> InitChain -> ShowS
Show, (forall x. InitChain -> Rep InitChain x)
-> (forall x. Rep InitChain x -> InitChain) -> Generic InitChain
forall x. Rep InitChain x -> InitChain
forall x. InitChain -> Rep InitChain x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InitChain x -> InitChain
$cfrom :: forall x. InitChain -> Rep InitChain x
Generic)
makeABCILenses ''InitChain
instance ToJSON InitChain where
toJSON :: InitChain -> Value
toJSON = Options -> InitChain -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> InitChain -> Value) -> Options -> InitChain -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "initChain"
instance FromJSON InitChain where
parseJSON :: Value -> Parser InitChain
parseJSON = String -> (Object -> Parser InitChain) -> Value -> Parser InitChain
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject "InitChain" ((Object -> Parser InitChain) -> Value -> Parser InitChain)
-> (Object -> Parser InitChain) -> Value -> Parser InitChain
forall a b. (a -> b) -> a -> b
$ \v :: Object
v -> Maybe Timestamp
-> Text
-> Maybe ConsensusParams
-> [ValidatorUpdate]
-> Base64String
-> InitChain
InitChain
(Maybe Timestamp
-> Text
-> Maybe ConsensusParams
-> [ValidatorUpdate]
-> Base64String
-> InitChain)
-> Parser (Maybe Timestamp)
-> Parser
(Text
-> Maybe ConsensusParams
-> [ValidatorUpdate]
-> Base64String
-> InitChain)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe Timestamp)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "time"
Parser
(Text
-> Maybe ConsensusParams
-> [ValidatorUpdate]
-> Base64String
-> InitChain)
-> Parser Text
-> Parser
(Maybe ConsensusParams
-> [ValidatorUpdate] -> Base64String -> InitChain)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: "chainId"
Parser
(Maybe ConsensusParams
-> [ValidatorUpdate] -> Base64String -> InitChain)
-> Parser (Maybe ConsensusParams)
-> Parser ([ValidatorUpdate] -> Base64String -> InitChain)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe ConsensusParams)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "consensusParams"
Parser ([ValidatorUpdate] -> Base64String -> InitChain)
-> Parser [ValidatorUpdate] -> Parser (Base64String -> InitChain)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe [ValidatorUpdate])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "validators" Parser (Maybe [ValidatorUpdate])
-> [ValidatorUpdate] -> Parser [ValidatorUpdate]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
Parser (Base64String -> InitChain)
-> Parser Base64String -> Parser InitChain
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser Base64String
forall a. FromJSON a => Object -> Text -> Parser a
.: "appState"
instance Wrapped InitChain where
type Unwrapped InitChain = PT.RequestInitChain
_Wrapped' :: p (Unwrapped InitChain) (f (Unwrapped InitChain))
-> p InitChain (f InitChain)
_Wrapped' = (InitChain -> RequestInitChain)
-> (RequestInitChain -> InitChain)
-> Iso InitChain InitChain RequestInitChain RequestInitChain
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso InitChain -> RequestInitChain
forall b a.
(Message b, HasField b "appStateBytes" a,
HasField b "chainId" Text,
HasField b "maybe'consensusParams" (Maybe ConsensusParams),
HasField b "maybe'time" (Maybe Timestamp),
HasField b "validators" [ValidatorUpdate], ByteArray a) =>
InitChain -> b
t RequestInitChain -> InitChain
forall (t :: * -> *) ba s.
(Traversable t, ByteArrayAccess ba, HasField s "appStateBytes" ba,
HasField s "chainId" Text,
HasField s "maybe'consensusParams" (Maybe ConsensusParams),
HasField s "maybe'time" (Maybe Timestamp),
HasField s "validators" (t ValidatorUpdate)) =>
s -> InitChain
f
where
t :: InitChain -> b
t InitChain {..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe Timestamp)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'time" a) =>
LensLike' f s a
PT.maybe'time LensLike' Identity b (Maybe Timestamp) -> Maybe Timestamp -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe Timestamp
initChainTime Maybe Timestamp
-> Getting (First Timestamp) (Maybe Timestamp) Timestamp
-> Maybe Timestamp
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Timestamp -> Const (First Timestamp) Timestamp)
-> Maybe Timestamp -> Const (First Timestamp) (Maybe Timestamp)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Timestamp -> Const (First Timestamp) Timestamp)
-> Maybe Timestamp -> Const (First Timestamp) (Maybe Timestamp))
-> ((Timestamp -> Const (First Timestamp) Timestamp)
-> Timestamp -> Const (First Timestamp) Timestamp)
-> Getting (First Timestamp) (Maybe Timestamp) Timestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Timestamp -> Const (First Timestamp) Timestamp)
-> Timestamp -> Const (First Timestamp) Timestamp
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Text
forall (f :: * -> *) s a.
(Functor f, HasField s "chainId" a) =>
LensLike' f s a
PT.chainId LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
initChainChainId
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe ConsensusParams)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'consensusParams" a) =>
LensLike' f s a
PT.maybe'consensusParams LensLike' Identity b (Maybe ConsensusParams)
-> Maybe ConsensusParams -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe ConsensusParams
initChainConsensusParams Maybe ConsensusParams
-> Getting
(First ConsensusParams) (Maybe ConsensusParams) ConsensusParams
-> Maybe ConsensusParams
forall s a. s -> Getting (First a) s a -> Maybe a
^? (ConsensusParams -> Const (First ConsensusParams) ConsensusParams)
-> Maybe ConsensusParams
-> Const (First ConsensusParams) (Maybe ConsensusParams)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((ConsensusParams -> Const (First ConsensusParams) ConsensusParams)
-> Maybe ConsensusParams
-> Const (First ConsensusParams) (Maybe ConsensusParams))
-> ((ConsensusParams
-> Const (First ConsensusParams) ConsensusParams)
-> ConsensusParams
-> Const (First ConsensusParams) ConsensusParams)
-> Getting
(First ConsensusParams) (Maybe ConsensusParams) ConsensusParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ConsensusParams -> Const (First ConsensusParams) ConsensusParams)
-> ConsensusParams -> Const (First ConsensusParams) ConsensusParams
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b [ValidatorUpdate]
forall (f :: * -> *) s a.
(Functor f, HasField s "validators" a) =>
LensLike' f s a
PT.validators LensLike' Identity b [ValidatorUpdate]
-> [ValidatorUpdate] -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ValidatorUpdate]
initChainValidators [ValidatorUpdate]
-> Getting
(Endo [ValidatorUpdate]) [ValidatorUpdate] ValidatorUpdate
-> [ValidatorUpdate]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (ValidatorUpdate -> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> [ValidatorUpdate]
-> Const (Endo [ValidatorUpdate]) [ValidatorUpdate]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> [ValidatorUpdate]
-> Const (Endo [ValidatorUpdate]) [ValidatorUpdate])
-> ((ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> Getting
(Endo [ValidatorUpdate]) [ValidatorUpdate] ValidatorUpdate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ValidatorUpdate -> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "appStateBytes" a) =>
LensLike' f s a
PT.appStateBytes LensLike' Identity b a -> a -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Base64String -> a
forall ba. ByteArray ba => Base64String -> ba
Base64.toBytes Base64String
initChainAppState
f :: s -> InitChain
f message :: s
message = InitChain :: Maybe Timestamp
-> Text
-> Maybe ConsensusParams
-> [ValidatorUpdate]
-> Base64String
-> InitChain
InitChain
{ initChainTime :: Maybe Timestamp
initChainTime = s
message s -> Getting (First Timestamp) s Timestamp -> Maybe Timestamp
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First Timestamp)) s (Maybe Timestamp)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'time" a) =>
LensLike' f s a
PT.maybe'time LensLike' (Const (First Timestamp)) s (Maybe Timestamp)
-> ((Timestamp -> Const (First Timestamp) Timestamp)
-> Maybe Timestamp -> Const (First Timestamp) (Maybe Timestamp))
-> Getting (First Timestamp) s Timestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Timestamp -> Const (First Timestamp) Timestamp)
-> Maybe Timestamp -> Const (First Timestamp) (Maybe Timestamp)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Timestamp -> Const (First Timestamp) Timestamp)
-> Maybe Timestamp -> Const (First Timestamp) (Maybe Timestamp))
-> ((Timestamp -> Const (First Timestamp) Timestamp)
-> Timestamp -> Const (First Timestamp) Timestamp)
-> (Timestamp -> Const (First Timestamp) Timestamp)
-> Maybe Timestamp
-> Const (First Timestamp) (Maybe Timestamp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Timestamp -> Const (First Timestamp) Timestamp)
-> Timestamp -> Const (First Timestamp) Timestamp
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, initChainChainId :: Text
initChainChainId = s
message s -> Getting Text s Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text s Text
forall (f :: * -> *) s a.
(Functor f, HasField s "chainId" a) =>
LensLike' f s a
PT.chainId
, initChainConsensusParams :: Maybe ConsensusParams
initChainConsensusParams = s
message s
-> Getting (First ConsensusParams) s ConsensusParams
-> Maybe ConsensusParams
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First ConsensusParams)) s (Maybe ConsensusParams)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'consensusParams" a) =>
LensLike' f s a
PT.maybe'consensusParams LensLike' (Const (First ConsensusParams)) s (Maybe ConsensusParams)
-> ((ConsensusParams
-> Const (First ConsensusParams) ConsensusParams)
-> Maybe ConsensusParams
-> Const (First ConsensusParams) (Maybe ConsensusParams))
-> Getting (First ConsensusParams) s ConsensusParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ConsensusParams -> Const (First ConsensusParams) ConsensusParams)
-> Maybe ConsensusParams
-> Const (First ConsensusParams) (Maybe ConsensusParams)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((ConsensusParams -> Const (First ConsensusParams) ConsensusParams)
-> Maybe ConsensusParams
-> Const (First ConsensusParams) (Maybe ConsensusParams))
-> ((ConsensusParams
-> Const (First ConsensusParams) ConsensusParams)
-> ConsensusParams
-> Const (First ConsensusParams) ConsensusParams)
-> (ConsensusParams
-> Const (First ConsensusParams) ConsensusParams)
-> Maybe ConsensusParams
-> Const (First ConsensusParams) (Maybe ConsensusParams)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ConsensusParams -> Const (First ConsensusParams) ConsensusParams)
-> ConsensusParams -> Const (First ConsensusParams) ConsensusParams
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, initChainValidators :: [ValidatorUpdate]
initChainValidators = s
message s
-> Getting (Endo [ValidatorUpdate]) s ValidatorUpdate
-> [ValidatorUpdate]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. LensLike' (Const (Endo [ValidatorUpdate])) s (t ValidatorUpdate)
forall (f :: * -> *) s a.
(Functor f, HasField s "validators" a) =>
LensLike' f s a
PT.validators LensLike' (Const (Endo [ValidatorUpdate])) s (t ValidatorUpdate)
-> ((ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> t ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) (t ValidatorUpdate))
-> Getting (Endo [ValidatorUpdate]) s ValidatorUpdate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ValidatorUpdate -> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> t ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) (t ValidatorUpdate)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> t ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) (t ValidatorUpdate))
-> ((ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> (ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> t ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) (t ValidatorUpdate)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ValidatorUpdate -> Const (Endo [ValidatorUpdate]) ValidatorUpdate)
-> ValidatorUpdate
-> Const (Endo [ValidatorUpdate]) ValidatorUpdate
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, initChainAppState :: Base64String
initChainAppState = ba -> Base64String
forall ba. ByteArrayAccess ba => ba -> Base64String
Base64.fromBytes (ba -> Base64String) -> ba -> Base64String
forall a b. (a -> b) -> a -> b
$ s
message s -> Getting ba s ba -> ba
forall s a. s -> Getting a s a -> a
^. Getting ba s ba
forall (f :: * -> *) s a.
(Functor f, HasField s "appStateBytes" a) =>
LensLike' f s a
PT.appStateBytes
}
instance Default InitChain where
def :: InitChain
def = RequestInitChain
forall msg. Message msg => msg
defMessage RequestInitChain
-> Getting InitChain RequestInitChain InitChain -> InitChain
forall s a. s -> Getting a s a -> a
^. Getting InitChain RequestInitChain InitChain
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data Query = Query
{ Query -> Base64String
queryData :: Base64String
, Query -> Text
queryPath :: Text
, Query -> WrappedVal Int64
queryHeight :: WrappedVal Int64
, Query -> Bool
queryProve :: Bool
} deriving (Query -> Query -> Bool
(Query -> Query -> Bool) -> (Query -> Query -> Bool) -> Eq Query
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Query -> Query -> Bool
$c/= :: Query -> Query -> Bool
== :: Query -> Query -> Bool
$c== :: Query -> Query -> Bool
Eq, Int -> Query -> ShowS
[Query] -> ShowS
Query -> String
(Int -> Query -> ShowS)
-> (Query -> String) -> ([Query] -> ShowS) -> Show Query
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Query] -> ShowS
$cshowList :: [Query] -> ShowS
show :: Query -> String
$cshow :: Query -> String
showsPrec :: Int -> Query -> ShowS
$cshowsPrec :: Int -> Query -> ShowS
Show, (forall x. Query -> Rep Query x)
-> (forall x. Rep Query x -> Query) -> Generic Query
forall x. Rep Query x -> Query
forall x. Query -> Rep Query x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Query x -> Query
$cfrom :: forall x. Query -> Rep Query x
Generic)
makeABCILenses ''Query
instance ToJSON Query where
toJSON :: Query -> Value
toJSON = Options -> Query -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Query -> Value) -> Options -> Query -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "query"
instance FromJSON Query where
parseJSON :: Value -> Parser Query
parseJSON = Options -> Value -> Parser Query
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Query)
-> Options -> Value -> Parser Query
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "query"
instance Wrapped Query where
type Unwrapped Query = PT.RequestQuery
_Wrapped' :: p (Unwrapped Query) (f (Unwrapped Query)) -> p Query (f Query)
_Wrapped' = (Query -> RequestQuery)
-> (RequestQuery -> Query)
-> Iso Query Query RequestQuery RequestQuery
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Query -> RequestQuery
forall b a.
(Message b, ByteArray a, HasField b "data'" a,
HasField b "height" Int64, HasField b "path" Text,
HasField b "prove" Bool) =>
Query -> b
t RequestQuery -> Query
forall ba s.
(ByteArrayAccess ba, HasField s "data'" ba,
HasField s "height" Int64, HasField s "path" Text,
HasField s "prove" Bool) =>
s -> Query
f
where
t :: Query -> b
t Query {..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "data'" a) =>
LensLike' f s a
PT.data' LensLike' Identity b a -> a -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Base64String -> a
forall ba. ByteArray ba => Base64String -> ba
Base64.toBytes Base64String
queryData
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Text
forall (f :: * -> *) s a.
(Functor f, HasField s "path" a) =>
LensLike' f s a
PT.path LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
queryPath
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "height" a) =>
LensLike' f s a
PT.height LensLike' Identity b Int64 -> Int64 -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ WrappedVal Int64 -> Int64
forall a. WrappedVal a -> a
unWrappedVal WrappedVal Int64
queryHeight
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Bool
forall (f :: * -> *) s a.
(Functor f, HasField s "prove" a) =>
LensLike' f s a
PT.prove LensLike' Identity b Bool -> Bool -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
queryProve
f :: s -> Query
f message :: s
message = Query :: Base64String -> Text -> WrappedVal Int64 -> Bool -> Query
Query { queryData :: Base64String
queryData = ba -> Base64String
forall ba. ByteArrayAccess ba => ba -> Base64String
Base64.fromBytes (ba -> Base64String) -> ba -> Base64String
forall a b. (a -> b) -> a -> b
$ s
message s -> Getting ba s ba -> ba
forall s a. s -> Getting a s a -> a
^. Getting ba s ba
forall (f :: * -> *) s a.
(Functor f, HasField s "data'" a) =>
LensLike' f s a
PT.data'
, queryPath :: Text
queryPath = s
message s -> Getting Text s Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text s Text
forall (f :: * -> *) s a.
(Functor f, HasField s "path" a) =>
LensLike' f s a
PT.path
, queryHeight :: WrappedVal Int64
queryHeight = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
message s -> Getting Int64 s Int64 -> Int64
forall s a. s -> Getting a s a -> a
^. Getting Int64 s Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "height" a) =>
LensLike' f s a
PT.height
, queryProve :: Bool
queryProve = s
message s -> Getting Bool s Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool s Bool
forall (f :: * -> *) s a.
(Functor f, HasField s "prove" a) =>
LensLike' f s a
PT.prove
}
instance Default Query where
def :: Query
def = RequestQuery
forall msg. Message msg => msg
defMessage RequestQuery -> Getting Query RequestQuery Query -> Query
forall s a. s -> Getting a s a -> a
^. Getting Query RequestQuery Query
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data BeginBlock = BeginBlock
{ BeginBlock -> HexString
beginBlockHash :: HexString
, :: Maybe Header
, BeginBlock -> Maybe LastCommitInfo
beginBlockLastCommitInfo :: Maybe LastCommitInfo
, BeginBlock -> [Evidence]
beginBlockByzantineValidators :: [Evidence]
} deriving (BeginBlock -> BeginBlock -> Bool
(BeginBlock -> BeginBlock -> Bool)
-> (BeginBlock -> BeginBlock -> Bool) -> Eq BeginBlock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BeginBlock -> BeginBlock -> Bool
$c/= :: BeginBlock -> BeginBlock -> Bool
== :: BeginBlock -> BeginBlock -> Bool
$c== :: BeginBlock -> BeginBlock -> Bool
Eq, Int -> BeginBlock -> ShowS
[BeginBlock] -> ShowS
BeginBlock -> String
(Int -> BeginBlock -> ShowS)
-> (BeginBlock -> String)
-> ([BeginBlock] -> ShowS)
-> Show BeginBlock
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BeginBlock] -> ShowS
$cshowList :: [BeginBlock] -> ShowS
show :: BeginBlock -> String
$cshow :: BeginBlock -> String
showsPrec :: Int -> BeginBlock -> ShowS
$cshowsPrec :: Int -> BeginBlock -> ShowS
Show, (forall x. BeginBlock -> Rep BeginBlock x)
-> (forall x. Rep BeginBlock x -> BeginBlock) -> Generic BeginBlock
forall x. Rep BeginBlock x -> BeginBlock
forall x. BeginBlock -> Rep BeginBlock x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BeginBlock x -> BeginBlock
$cfrom :: forall x. BeginBlock -> Rep BeginBlock x
Generic)
instance ToJSON BeginBlock where
toJSON :: BeginBlock -> Value
toJSON = Options -> BeginBlock -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> BeginBlock -> Value) -> Options -> BeginBlock -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "beginBlock"
instance FromJSON BeginBlock where
parseJSON :: Value -> Parser BeginBlock
parseJSON = String
-> (Object -> Parser BeginBlock) -> Value -> Parser BeginBlock
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject "BeginBlock" ((Object -> Parser BeginBlock) -> Value -> Parser BeginBlock)
-> (Object -> Parser BeginBlock) -> Value -> Parser BeginBlock
forall a b. (a -> b) -> a -> b
$ \v :: Object
v -> HexString
-> Maybe Header -> Maybe LastCommitInfo -> [Evidence] -> BeginBlock
BeginBlock
(HexString
-> Maybe Header
-> Maybe LastCommitInfo
-> [Evidence]
-> BeginBlock)
-> Parser HexString
-> Parser
(Maybe Header -> Maybe LastCommitInfo -> [Evidence] -> BeginBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser HexString
forall a. FromJSON a => Object -> Text -> Parser a
.: "hash"
Parser
(Maybe Header -> Maybe LastCommitInfo -> [Evidence] -> BeginBlock)
-> Parser (Maybe Header)
-> Parser (Maybe LastCommitInfo -> [Evidence] -> BeginBlock)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Header)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "header"
Parser (Maybe LastCommitInfo -> [Evidence] -> BeginBlock)
-> Parser (Maybe LastCommitInfo)
-> Parser ([Evidence] -> BeginBlock)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe LastCommitInfo)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "lastCommitInfo"
Parser ([Evidence] -> BeginBlock)
-> Parser [Evidence] -> Parser BeginBlock
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe [Evidence])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "byzantineValidators" Parser (Maybe [Evidence]) -> [Evidence] -> Parser [Evidence]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
instance Wrapped BeginBlock where
type Unwrapped BeginBlock = PT.RequestBeginBlock
_Wrapped' :: p (Unwrapped BeginBlock) (f (Unwrapped BeginBlock))
-> p BeginBlock (f BeginBlock)
_Wrapped' = (BeginBlock -> RequestBeginBlock)
-> (RequestBeginBlock -> BeginBlock)
-> Iso BeginBlock BeginBlock RequestBeginBlock RequestBeginBlock
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso BeginBlock -> RequestBeginBlock
forall b a.
(Message b, ByteArray a,
HasField b "byzantineValidators" [Evidence], HasField b "hash" a,
HasField b "maybe'header" (Maybe Header),
HasField b "maybe'lastCommitInfo" (Maybe LastCommitInfo)) =>
BeginBlock -> b
t RequestBeginBlock -> BeginBlock
forall ba s (t :: * -> *).
(ByteArrayAccess ba, HasField s "byzantineValidators" (t Evidence),
HasField s "hash" ba, HasField s "maybe'header" (Maybe Header),
HasField s "maybe'lastCommitInfo" (Maybe LastCommitInfo),
Traversable t) =>
s -> BeginBlock
f
where
t :: BeginBlock -> b
t BeginBlock {..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "hash" a) =>
LensLike' f s a
PT.hash LensLike' Identity b a -> a -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ HexString -> a
forall ba. ByteArray ba => HexString -> ba
Hex.toBytes HexString
beginBlockHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe Header)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'header" a) =>
LensLike' f s a
PT.maybe'header LensLike' Identity b (Maybe Header) -> Maybe Header -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe Header
beginBlockHeader Maybe Header
-> Getting (First Header) (Maybe Header) Header -> Maybe Header
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Header -> Const (First Header) Header)
-> Maybe Header -> Const (First Header) (Maybe Header)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Header -> Const (First Header) Header)
-> Maybe Header -> Const (First Header) (Maybe Header))
-> ((Header -> Const (First Header) Header)
-> Header -> Const (First Header) Header)
-> Getting (First Header) (Maybe Header) Header
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Header -> Const (First Header) Header)
-> Header -> Const (First Header) Header
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe LastCommitInfo)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'lastCommitInfo" a) =>
LensLike' f s a
PT.maybe'lastCommitInfo LensLike' Identity b (Maybe LastCommitInfo)
-> Maybe LastCommitInfo -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe LastCommitInfo
beginBlockLastCommitInfo Maybe LastCommitInfo
-> Getting
(First LastCommitInfo) (Maybe LastCommitInfo) LastCommitInfo
-> Maybe LastCommitInfo
forall s a. s -> Getting (First a) s a -> Maybe a
^? (LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> Maybe LastCommitInfo
-> Const (First LastCommitInfo) (Maybe LastCommitInfo)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> Maybe LastCommitInfo
-> Const (First LastCommitInfo) (Maybe LastCommitInfo))
-> ((LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> Getting
(First LastCommitInfo) (Maybe LastCommitInfo) LastCommitInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b [Evidence]
forall (f :: * -> *) s a.
(Functor f, HasField s "byzantineValidators" a) =>
LensLike' f s a
PT.byzantineValidators LensLike' Identity b [Evidence] -> [Evidence] -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Evidence]
beginBlockByzantineValidators [Evidence]
-> Getting (Endo [Evidence]) [Evidence] Evidence -> [Evidence]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (Evidence -> Const (Endo [Evidence]) Evidence)
-> [Evidence] -> Const (Endo [Evidence]) [Evidence]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((Evidence -> Const (Endo [Evidence]) Evidence)
-> [Evidence] -> Const (Endo [Evidence]) [Evidence])
-> ((Evidence -> Const (Endo [Evidence]) Evidence)
-> Evidence -> Const (Endo [Evidence]) Evidence)
-> Getting (Endo [Evidence]) [Evidence] Evidence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Evidence -> Const (Endo [Evidence]) Evidence)
-> Evidence -> Const (Endo [Evidence]) Evidence
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
f :: s -> BeginBlock
f message :: s
message = BeginBlock :: HexString
-> Maybe Header -> Maybe LastCommitInfo -> [Evidence] -> BeginBlock
BeginBlock
{ beginBlockHash :: HexString
beginBlockHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
message s -> Getting ba s ba -> ba
forall s a. s -> Getting a s a -> a
^. Getting ba s ba
forall (f :: * -> *) s a.
(Functor f, HasField s "hash" a) =>
LensLike' f s a
PT.hash
, beginBlockHeader :: Maybe Header
beginBlockHeader = s
message s -> Getting (First Header) s Header -> Maybe Header
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First Header)) s (Maybe Header)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'header" a) =>
LensLike' f s a
PT.maybe'header LensLike' (Const (First Header)) s (Maybe Header)
-> ((Header -> Const (First Header) Header)
-> Maybe Header -> Const (First Header) (Maybe Header))
-> Getting (First Header) s Header
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Header -> Const (First Header) Header)
-> Maybe Header -> Const (First Header) (Maybe Header)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Header -> Const (First Header) Header)
-> Maybe Header -> Const (First Header) (Maybe Header))
-> ((Header -> Const (First Header) Header)
-> Header -> Const (First Header) Header)
-> (Header -> Const (First Header) Header)
-> Maybe Header
-> Const (First Header) (Maybe Header)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Header -> Const (First Header) Header)
-> Header -> Const (First Header) Header
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, beginBlockLastCommitInfo :: Maybe LastCommitInfo
beginBlockLastCommitInfo = s
message s
-> Getting (First LastCommitInfo) s LastCommitInfo
-> Maybe LastCommitInfo
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First LastCommitInfo)) s (Maybe LastCommitInfo)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'lastCommitInfo" a) =>
LensLike' f s a
PT.maybe'lastCommitInfo LensLike' (Const (First LastCommitInfo)) s (Maybe LastCommitInfo)
-> ((LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> Maybe LastCommitInfo
-> Const (First LastCommitInfo) (Maybe LastCommitInfo))
-> Getting (First LastCommitInfo) s LastCommitInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> Maybe LastCommitInfo
-> Const (First LastCommitInfo) (Maybe LastCommitInfo)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> Maybe LastCommitInfo
-> Const (First LastCommitInfo) (Maybe LastCommitInfo))
-> ((LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> (LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> Maybe LastCommitInfo
-> Const (First LastCommitInfo) (Maybe LastCommitInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo)
-> LastCommitInfo -> Const (First LastCommitInfo) LastCommitInfo
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, beginBlockByzantineValidators :: [Evidence]
beginBlockByzantineValidators = s
message s -> Getting (Endo [Evidence]) s Evidence -> [Evidence]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. LensLike' (Const (Endo [Evidence])) s (t Evidence)
forall (f :: * -> *) s a.
(Functor f, HasField s "byzantineValidators" a) =>
LensLike' f s a
PT.byzantineValidators LensLike' (Const (Endo [Evidence])) s (t Evidence)
-> ((Evidence -> Const (Endo [Evidence]) Evidence)
-> t Evidence -> Const (Endo [Evidence]) (t Evidence))
-> Getting (Endo [Evidence]) s Evidence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Evidence -> Const (Endo [Evidence]) Evidence)
-> t Evidence -> Const (Endo [Evidence]) (t Evidence)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((Evidence -> Const (Endo [Evidence]) Evidence)
-> t Evidence -> Const (Endo [Evidence]) (t Evidence))
-> ((Evidence -> Const (Endo [Evidence]) Evidence)
-> Evidence -> Const (Endo [Evidence]) Evidence)
-> (Evidence -> Const (Endo [Evidence]) Evidence)
-> t Evidence
-> Const (Endo [Evidence]) (t Evidence)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Evidence -> Const (Endo [Evidence]) Evidence)
-> Evidence -> Const (Endo [Evidence]) Evidence
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
}
instance Default BeginBlock where
def :: BeginBlock
def = RequestBeginBlock
forall msg. Message msg => msg
defMessage RequestBeginBlock
-> Getting BeginBlock RequestBeginBlock BeginBlock -> BeginBlock
forall s a. s -> Getting a s a -> a
^. Getting BeginBlock RequestBeginBlock BeginBlock
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data CheckTx = CheckTx
{ CheckTx -> Base64String
checkTxTx :: Base64String
} deriving (CheckTx -> CheckTx -> Bool
(CheckTx -> CheckTx -> Bool)
-> (CheckTx -> CheckTx -> Bool) -> Eq CheckTx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckTx -> CheckTx -> Bool
$c/= :: CheckTx -> CheckTx -> Bool
== :: CheckTx -> CheckTx -> Bool
$c== :: CheckTx -> CheckTx -> Bool
Eq, Int -> CheckTx -> ShowS
[CheckTx] -> ShowS
CheckTx -> String
(Int -> CheckTx -> ShowS)
-> (CheckTx -> String) -> ([CheckTx] -> ShowS) -> Show CheckTx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckTx] -> ShowS
$cshowList :: [CheckTx] -> ShowS
show :: CheckTx -> String
$cshow :: CheckTx -> String
showsPrec :: Int -> CheckTx -> ShowS
$cshowsPrec :: Int -> CheckTx -> ShowS
Show, (forall x. CheckTx -> Rep CheckTx x)
-> (forall x. Rep CheckTx x -> CheckTx) -> Generic CheckTx
forall x. Rep CheckTx x -> CheckTx
forall x. CheckTx -> Rep CheckTx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckTx x -> CheckTx
$cfrom :: forall x. CheckTx -> Rep CheckTx x
Generic)
makeABCILenses ''CheckTx
instance ToJSON CheckTx where
toJSON :: CheckTx -> Value
toJSON = Options -> CheckTx -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> CheckTx -> Value) -> Options -> CheckTx -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "checkTx"
instance FromJSON CheckTx where
parseJSON :: Value -> Parser CheckTx
parseJSON = Options -> Value -> Parser CheckTx
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser CheckTx)
-> Options -> Value -> Parser CheckTx
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "checkTx"
instance Wrapped CheckTx where
type Unwrapped CheckTx = PT.RequestCheckTx
_Wrapped' :: p (Unwrapped CheckTx) (f (Unwrapped CheckTx))
-> p CheckTx (f CheckTx)
_Wrapped' = (CheckTx -> RequestCheckTx)
-> (RequestCheckTx -> CheckTx)
-> Iso CheckTx CheckTx RequestCheckTx RequestCheckTx
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso CheckTx -> RequestCheckTx
forall b a.
(Message b, HasField b "tx" a, ByteArray a) =>
CheckTx -> b
t RequestCheckTx -> CheckTx
forall ba s.
(ByteArrayAccess ba, HasField s "tx" ba) =>
s -> CheckTx
f
where
t :: CheckTx -> b
t CheckTx {..} = b
forall msg. Message msg => msg
defMessage b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "tx" a) =>
LensLike' f s a
PT.tx LensLike' Identity b a -> a -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Base64String -> a
forall ba. ByteArray ba => Base64String -> ba
Base64.toBytes Base64String
checkTxTx
f :: s -> CheckTx
f message :: s
message = CheckTx :: Base64String -> CheckTx
CheckTx { checkTxTx :: Base64String
checkTxTx = ba -> Base64String
forall ba. ByteArrayAccess ba => ba -> Base64String
Base64.fromBytes (ba -> Base64String) -> ba -> Base64String
forall a b. (a -> b) -> a -> b
$ s
message s -> Getting ba s ba -> ba
forall s a. s -> Getting a s a -> a
^. Getting ba s ba
forall (f :: * -> *) s a.
(Functor f, HasField s "tx" a) =>
LensLike' f s a
PT.tx }
instance Default CheckTx where
def :: CheckTx
def = RequestCheckTx
forall msg. Message msg => msg
defMessage RequestCheckTx -> Getting CheckTx RequestCheckTx CheckTx -> CheckTx
forall s a. s -> Getting a s a -> a
^. Getting CheckTx RequestCheckTx CheckTx
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data DeliverTx = DeliverTx
{ DeliverTx -> Base64String
deliverTxTx :: Base64String
} deriving (DeliverTx -> DeliverTx -> Bool
(DeliverTx -> DeliverTx -> Bool)
-> (DeliverTx -> DeliverTx -> Bool) -> Eq DeliverTx
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeliverTx -> DeliverTx -> Bool
$c/= :: DeliverTx -> DeliverTx -> Bool
== :: DeliverTx -> DeliverTx -> Bool
$c== :: DeliverTx -> DeliverTx -> Bool
Eq, Int -> DeliverTx -> ShowS
[DeliverTx] -> ShowS
DeliverTx -> String
(Int -> DeliverTx -> ShowS)
-> (DeliverTx -> String)
-> ([DeliverTx] -> ShowS)
-> Show DeliverTx
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeliverTx] -> ShowS
$cshowList :: [DeliverTx] -> ShowS
show :: DeliverTx -> String
$cshow :: DeliverTx -> String
showsPrec :: Int -> DeliverTx -> ShowS
$cshowsPrec :: Int -> DeliverTx -> ShowS
Show, (forall x. DeliverTx -> Rep DeliverTx x)
-> (forall x. Rep DeliverTx x -> DeliverTx) -> Generic DeliverTx
forall x. Rep DeliverTx x -> DeliverTx
forall x. DeliverTx -> Rep DeliverTx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeliverTx x -> DeliverTx
$cfrom :: forall x. DeliverTx -> Rep DeliverTx x
Generic)
makeABCILenses ''DeliverTx
instance ToJSON DeliverTx where
toJSON :: DeliverTx -> Value
toJSON = Options -> DeliverTx -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> DeliverTx -> Value) -> Options -> DeliverTx -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "deliverTx"
instance FromJSON DeliverTx where
parseJSON :: Value -> Parser DeliverTx
parseJSON = Options -> Value -> Parser DeliverTx
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser DeliverTx)
-> Options -> Value -> Parser DeliverTx
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "deliverTx"
instance Wrapped DeliverTx where
type Unwrapped DeliverTx = PT.RequestDeliverTx
_Wrapped' :: p (Unwrapped DeliverTx) (f (Unwrapped DeliverTx))
-> p DeliverTx (f DeliverTx)
_Wrapped' = (DeliverTx -> RequestDeliverTx)
-> (RequestDeliverTx -> DeliverTx)
-> Iso DeliverTx DeliverTx RequestDeliverTx RequestDeliverTx
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso DeliverTx -> RequestDeliverTx
forall b a.
(Message b, HasField b "tx" a, ByteArray a) =>
DeliverTx -> b
t RequestDeliverTx -> DeliverTx
forall ba s.
(ByteArrayAccess ba, HasField s "tx" ba) =>
s -> DeliverTx
f
where
t :: DeliverTx -> b
t DeliverTx {..} = b
forall msg. Message msg => msg
defMessage b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "tx" a) =>
LensLike' f s a
PT.tx LensLike' Identity b a -> a -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Base64String -> a
forall ba. ByteArray ba => Base64String -> ba
Base64.toBytes Base64String
deliverTxTx
f :: s -> DeliverTx
f message :: s
message = DeliverTx :: Base64String -> DeliverTx
DeliverTx { deliverTxTx :: Base64String
deliverTxTx = ba -> Base64String
forall ba. ByteArrayAccess ba => ba -> Base64String
Base64.fromBytes (ba -> Base64String) -> ba -> Base64String
forall a b. (a -> b) -> a -> b
$ s
message s -> Getting ba s ba -> ba
forall s a. s -> Getting a s a -> a
^. Getting ba s ba
forall (f :: * -> *) s a.
(Functor f, HasField s "tx" a) =>
LensLike' f s a
PT.tx }
instance Default DeliverTx where
def :: DeliverTx
def = RequestDeliverTx
forall msg. Message msg => msg
defMessage RequestDeliverTx
-> Getting DeliverTx RequestDeliverTx DeliverTx -> DeliverTx
forall s a. s -> Getting a s a -> a
^. Getting DeliverTx RequestDeliverTx DeliverTx
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data EndBlock = EndBlock
{ EndBlock -> WrappedVal Int64
endBlockHeight :: WrappedVal Int64
} deriving (EndBlock -> EndBlock -> Bool
(EndBlock -> EndBlock -> Bool)
-> (EndBlock -> EndBlock -> Bool) -> Eq EndBlock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EndBlock -> EndBlock -> Bool
$c/= :: EndBlock -> EndBlock -> Bool
== :: EndBlock -> EndBlock -> Bool
$c== :: EndBlock -> EndBlock -> Bool
Eq, Int -> EndBlock -> ShowS
[EndBlock] -> ShowS
EndBlock -> String
(Int -> EndBlock -> ShowS)
-> (EndBlock -> String) -> ([EndBlock] -> ShowS) -> Show EndBlock
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EndBlock] -> ShowS
$cshowList :: [EndBlock] -> ShowS
show :: EndBlock -> String
$cshow :: EndBlock -> String
showsPrec :: Int -> EndBlock -> ShowS
$cshowsPrec :: Int -> EndBlock -> ShowS
Show, (forall x. EndBlock -> Rep EndBlock x)
-> (forall x. Rep EndBlock x -> EndBlock) -> Generic EndBlock
forall x. Rep EndBlock x -> EndBlock
forall x. EndBlock -> Rep EndBlock x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EndBlock x -> EndBlock
$cfrom :: forall x. EndBlock -> Rep EndBlock x
Generic)
makeABCILenses ''EndBlock
instance ToJSON EndBlock where
toJSON :: EndBlock -> Value
toJSON = Options -> EndBlock -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> EndBlock -> Value) -> Options -> EndBlock -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "endBlock"
instance FromJSON EndBlock where
parseJSON :: Value -> Parser EndBlock
parseJSON = Options -> Value -> Parser EndBlock
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser EndBlock)
-> Options -> Value -> Parser EndBlock
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "endBlock"
instance Wrapped EndBlock where
type Unwrapped EndBlock = PT.RequestEndBlock
_Wrapped' :: p (Unwrapped EndBlock) (f (Unwrapped EndBlock))
-> p EndBlock (f EndBlock)
_Wrapped' = (EndBlock -> RequestEndBlock)
-> (RequestEndBlock -> EndBlock)
-> Iso EndBlock EndBlock RequestEndBlock RequestEndBlock
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso EndBlock -> RequestEndBlock
forall b. (Message b, HasField b "height" Int64) => EndBlock -> b
t RequestEndBlock -> EndBlock
forall s. HasField s "height" Int64 => s -> EndBlock
f
where
t :: EndBlock -> b
t EndBlock {..} = b
forall msg. Message msg => msg
defMessage b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "height" a) =>
LensLike' f s a
PT.height LensLike' Identity b Int64 -> Int64 -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ WrappedVal Int64 -> Int64
forall a. WrappedVal a -> a
unWrappedVal WrappedVal Int64
endBlockHeight
f :: s -> EndBlock
f message :: s
message =
EndBlock :: WrappedVal Int64 -> EndBlock
EndBlock { endBlockHeight :: WrappedVal Int64
endBlockHeight = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
message s -> Getting Int64 s Int64 -> Int64
forall s a. s -> Getting a s a -> a
^. Getting Int64 s Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "height" a) =>
LensLike' f s a
PT.height }
instance Default EndBlock where
def :: EndBlock
def = RequestEndBlock
forall msg. Message msg => msg
defMessage RequestEndBlock
-> Getting EndBlock RequestEndBlock EndBlock -> EndBlock
forall s a. s -> Getting a s a -> a
^. Getting EndBlock RequestEndBlock EndBlock
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
data Commit =
Commit deriving (Commit -> Commit -> Bool
(Commit -> Commit -> Bool)
-> (Commit -> Commit -> Bool) -> Eq Commit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Commit -> Commit -> Bool
$c/= :: Commit -> Commit -> Bool
== :: Commit -> Commit -> Bool
$c== :: Commit -> Commit -> Bool
Eq, Int -> Commit -> ShowS
[Commit] -> ShowS
Commit -> String
(Int -> Commit -> ShowS)
-> (Commit -> String) -> ([Commit] -> ShowS) -> Show Commit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Commit] -> ShowS
$cshowList :: [Commit] -> ShowS
show :: Commit -> String
$cshow :: Commit -> String
showsPrec :: Int -> Commit -> ShowS
$cshowsPrec :: Int -> Commit -> ShowS
Show, (forall x. Commit -> Rep Commit x)
-> (forall x. Rep Commit x -> Commit) -> Generic Commit
forall x. Rep Commit x -> Commit
forall x. Commit -> Rep Commit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Commit x -> Commit
$cfrom :: forall x. Commit -> Rep Commit x
Generic)
makeABCILenses ''Commit
instance ToJSON Commit where
toJSON :: Commit -> Value
toJSON = Options -> Commit -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Commit -> Value) -> Options -> Commit -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "commit"
instance FromJSON Commit where
parseJSON :: Value -> Parser Commit
parseJSON = Options -> Value -> Parser Commit
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Commit)
-> Options -> Value -> Parser Commit
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "commit"
instance Wrapped Commit where
type Unwrapped Commit = PT.RequestCommit
_Wrapped' :: p (Unwrapped Commit) (f (Unwrapped Commit)) -> p Commit (f Commit)
_Wrapped' = (Commit -> RequestCommit)
-> (RequestCommit -> Commit)
-> Iso Commit Commit RequestCommit RequestCommit
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Commit -> RequestCommit
forall msg. Message msg => Commit -> msg
t RequestCommit -> Commit
forall p. p -> Commit
f
where
t :: Commit -> msg
t Commit = msg
forall msg. Message msg => msg
defMessage
f :: p -> Commit
f _ = Commit
Commit
instance Default Commit where
def :: Commit
def = RequestCommit
forall msg. Message msg => msg
defMessage RequestCommit -> Getting Commit RequestCommit Commit -> Commit
forall s a. s -> Getting a s a -> a
^. Getting Commit RequestCommit Commit
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'