module Network.ABCI.Types.Messages.FieldTypes where
import Control.Lens (iso,
(&),
(.~),
(^.),
(^..),
(^?),
_Just)
import Control.Lens.Wrapped (Wrapped (..),
_Unwrapped')
import Data.Aeson (FromJSON (..),
ToJSON (..),
Value (..),
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.Int (Int32,
Int64)
import Data.ProtoLens.Message (Message (defMessage))
import Data.Text (Text,
pack,
unpack)
import Data.Time.Clock (DiffTime,
diffTimeToPicoseconds,
picosecondsToDiffTime)
import Data.Time.Format (defaultTimeLocale,
parseTimeOrError)
import Data.Word (Word64)
import GHC.Generics (Generic)
import Network.ABCI.Types.Messages.Common (defaultABCIOptions)
import qualified Proto.Google.Protobuf.Timestamp as T
import qualified Proto.Google.Protobuf.Timestamp_Fields as T
import qualified Proto.Tendermint.Tendermint.Crypto.Merkle.Merkle as MT
import qualified Proto.Tendermint.Tendermint.Crypto.Merkle.Merkle_Fields as MT
import qualified Proto.Tendermint.Tendermint.Libs.Common.Types as CT
import qualified Proto.Tendermint.Tendermint.Libs.Common.Types_Fields as CT
import qualified Proto.Types as PT
import qualified Proto.Types_Fields as PT
newtype WrappedVal a = WrappedVal { WrappedVal a -> a
unWrappedVal :: a } deriving (WrappedVal a -> WrappedVal a -> Bool
(WrappedVal a -> WrappedVal a -> Bool)
-> (WrappedVal a -> WrappedVal a -> Bool) -> Eq (WrappedVal a)
forall a. Eq a => WrappedVal a -> WrappedVal a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WrappedVal a -> WrappedVal a -> Bool
$c/= :: forall a. Eq a => WrappedVal a -> WrappedVal a -> Bool
== :: WrappedVal a -> WrappedVal a -> Bool
$c== :: forall a. Eq a => WrappedVal a -> WrappedVal a -> Bool
Eq, Int -> WrappedVal a -> ShowS
[WrappedVal a] -> ShowS
WrappedVal a -> String
(Int -> WrappedVal a -> ShowS)
-> (WrappedVal a -> String)
-> ([WrappedVal a] -> ShowS)
-> Show (WrappedVal a)
forall a. Show a => Int -> WrappedVal a -> ShowS
forall a. Show a => [WrappedVal a] -> ShowS
forall a. Show a => WrappedVal a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WrappedVal a] -> ShowS
$cshowList :: forall a. Show a => [WrappedVal a] -> ShowS
show :: WrappedVal a -> String
$cshow :: forall a. Show a => WrappedVal a -> String
showsPrec :: Int -> WrappedVal a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> WrappedVal a -> ShowS
Show, (forall x. WrappedVal a -> Rep (WrappedVal a) x)
-> (forall x. Rep (WrappedVal a) x -> WrappedVal a)
-> Generic (WrappedVal a)
forall x. Rep (WrappedVal a) x -> WrappedVal a
forall x. WrappedVal a -> Rep (WrappedVal a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (WrappedVal a) x -> WrappedVal a
forall a x. WrappedVal a -> Rep (WrappedVal a) x
$cto :: forall a x. Rep (WrappedVal a) x -> WrappedVal a
$cfrom :: forall a x. WrappedVal a -> Rep (WrappedVal a) x
Generic)
instance Num a => Num (WrappedVal a) where
(WrappedVal x :: a
x) + :: WrappedVal a -> WrappedVal a -> WrappedVal a
+ (WrappedVal y :: a
y) = a -> WrappedVal a
forall a. a -> WrappedVal a
WrappedVal (a -> WrappedVal a) -> a -> WrappedVal a
forall a b. (a -> b) -> a -> b
$ a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y
(WrappedVal x :: a
x) - :: WrappedVal a -> WrappedVal a -> WrappedVal a
- (WrappedVal y :: a
y) = a -> WrappedVal a
forall a. a -> WrappedVal a
WrappedVal (a -> WrappedVal a) -> a -> WrappedVal a
forall a b. (a -> b) -> a -> b
$ a
x a -> a -> a
forall a. Num a => a -> a -> a
- a
y
(WrappedVal x :: a
x) * :: WrappedVal a -> WrappedVal a -> WrappedVal a
* (WrappedVal y :: a
y) = a -> WrappedVal a
forall a. a -> WrappedVal a
WrappedVal (a -> WrappedVal a) -> a -> WrappedVal a
forall a b. (a -> b) -> a -> b
$ a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
y
abs :: WrappedVal a -> WrappedVal a
abs (WrappedVal x :: a
x) = a -> WrappedVal a
forall a. a -> WrappedVal a
WrappedVal (a -> WrappedVal a) -> a -> WrappedVal a
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Num a => a -> a
abs a
x
fromInteger :: Integer -> WrappedVal a
fromInteger x :: Integer
x = a -> WrappedVal a
forall a. a -> WrappedVal a
WrappedVal (a -> WrappedVal a) -> a -> WrappedVal a
forall a b. (a -> b) -> a -> b
$ Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
x
signum :: WrappedVal a -> WrappedVal a
signum (WrappedVal x :: a
x) = a -> WrappedVal a
forall a. a -> WrappedVal a
WrappedVal (a -> WrappedVal a) -> a -> WrappedVal a
forall a b. (a -> b) -> a -> b
$ a -> a
forall a. Num a => a -> a
signum a
x
instance ToJSON (WrappedVal Int) where
toJSON :: WrappedVal Int -> Value
toJSON (WrappedVal n :: Int
n) = Text -> Value
String (Text -> Value) -> (Int -> Text) -> Int -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Text) -> (Int -> String) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show (Int -> Value) -> Int -> Value
forall a b. (a -> b) -> a -> b
$ Int
n
instance FromJSON (WrappedVal Int) where
parseJSON :: Value -> Parser (WrappedVal Int)
parseJSON (String t :: Text
t) = WrappedVal Int -> Parser (WrappedVal Int)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WrappedVal Int -> Parser (WrappedVal Int))
-> (Text -> WrappedVal Int) -> Text -> Parser (WrappedVal Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> WrappedVal Int
forall a. a -> WrappedVal a
WrappedVal (Int -> WrappedVal Int) -> (Text -> Int) -> Text -> WrappedVal Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Int
forall a. Read a => String -> a
read (String -> Int) -> (Text -> String) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> Parser (WrappedVal Int))
-> Text -> Parser (WrappedVal Int)
forall a b. (a -> b) -> a -> b
$ Text
t
parseJSON a :: Value
a = Int -> WrappedVal Int
forall a. a -> WrappedVal a
WrappedVal (Int -> WrappedVal Int) -> Parser Int -> Parser (WrappedVal Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
a
instance ToJSON (WrappedVal Int32) where
toJSON :: WrappedVal Int32 -> Value
toJSON (WrappedVal n :: Int32
n) = Text -> Value
String (Text -> Value) -> (Int32 -> Text) -> Int32 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Text) -> (Int32 -> String) -> Int32 -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> String
forall a. Show a => a -> String
show (Int32 -> Value) -> Int32 -> Value
forall a b. (a -> b) -> a -> b
$ Int32
n
instance FromJSON (WrappedVal Int32) where
parseJSON :: Value -> Parser (WrappedVal Int32)
parseJSON (String t :: Text
t) = WrappedVal Int32 -> Parser (WrappedVal Int32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WrappedVal Int32 -> Parser (WrappedVal Int32))
-> (Text -> WrappedVal Int32) -> Text -> Parser (WrappedVal Int32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> WrappedVal Int32
forall a. a -> WrappedVal a
WrappedVal (Int32 -> WrappedVal Int32)
-> (Text -> Int32) -> Text -> WrappedVal Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Int32
forall a. Read a => String -> a
read (String -> Int32) -> (Text -> String) -> Text -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> Parser (WrappedVal Int32))
-> Text -> Parser (WrappedVal Int32)
forall a b. (a -> b) -> a -> b
$ Text
t
parseJSON a :: Value
a = Int32 -> WrappedVal Int32
forall a. a -> WrappedVal a
WrappedVal (Int32 -> WrappedVal Int32)
-> Parser Int32 -> Parser (WrappedVal Int32)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int32
forall a. FromJSON a => Value -> Parser a
parseJSON Value
a
instance ToJSON (WrappedVal Int64) where
toJSON :: WrappedVal Int64 -> Value
toJSON (WrappedVal n :: Int64
n) = Text -> Value
String (Text -> Value) -> (Int64 -> Text) -> Int64 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Text) -> (Int64 -> String) -> Int64 -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> String
forall a. Show a => a -> String
show (Int64 -> Value) -> Int64 -> Value
forall a b. (a -> b) -> a -> b
$ Int64
n
instance FromJSON (WrappedVal Int64) where
parseJSON :: Value -> Parser (WrappedVal Int64)
parseJSON (String t :: Text
t) = WrappedVal Int64 -> Parser (WrappedVal Int64)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WrappedVal Int64 -> Parser (WrappedVal Int64))
-> (Text -> WrappedVal Int64) -> Text -> Parser (WrappedVal Int64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64)
-> (Text -> Int64) -> Text -> WrappedVal Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Int64
forall a. Read a => String -> a
read (String -> Int64) -> (Text -> String) -> Text -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> Parser (WrappedVal Int64))
-> Text -> Parser (WrappedVal Int64)
forall a b. (a -> b) -> a -> b
$ Text
t
parseJSON a :: Value
a = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64)
-> Parser Int64 -> Parser (WrappedVal Int64)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int64
forall a. FromJSON a => Value -> Parser a
parseJSON Value
a
instance ToJSON (WrappedVal Word64) where
toJSON :: WrappedVal Word64 -> Value
toJSON (WrappedVal n :: Word64
n) = Text -> Value
String (Text -> Value) -> (Word64 -> Text) -> Word64 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> Text) -> (Word64 -> String) -> Word64 -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> String
forall a. Show a => a -> String
show (Word64 -> Value) -> Word64 -> Value
forall a b. (a -> b) -> a -> b
$ Word64
n
instance FromJSON (WrappedVal Word64) where
parseJSON :: Value -> Parser (WrappedVal Word64)
parseJSON (String t :: Text
t) = WrappedVal Word64 -> Parser (WrappedVal Word64)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WrappedVal Word64 -> Parser (WrappedVal Word64))
-> (Text -> WrappedVal Word64)
-> Text
-> Parser (WrappedVal Word64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> WrappedVal Word64
forall a. a -> WrappedVal a
WrappedVal (Word64 -> WrappedVal Word64)
-> (Text -> Word64) -> Text -> WrappedVal Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Word64
forall a. Read a => String -> a
read (String -> Word64) -> (Text -> String) -> Text -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> Parser (WrappedVal Word64))
-> Text -> Parser (WrappedVal Word64)
forall a b. (a -> b) -> a -> b
$ Text
t
parseJSON a :: Value
a = Word64 -> WrappedVal Word64
forall a. a -> WrappedVal a
WrappedVal (Word64 -> WrappedVal Word64)
-> Parser Word64 -> Parser (WrappedVal Word64)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Word64
forall a. FromJSON a => Value -> Parser a
parseJSON Value
a
instance ToJSON a => ToJSON (WrappedVal [a]) where
toJSON :: WrappedVal [a] -> Value
toJSON (WrappedVal as :: [a]
as) = [a] -> Value
forall a. ToJSON a => a -> Value
toJSON [a]
as
instance FromJSON a => FromJSON (WrappedVal [a]) where
parseJSON :: Value -> Parser (WrappedVal [a])
parseJSON as :: Value
as@(Array _) = [a] -> WrappedVal [a]
forall a. a -> WrappedVal a
WrappedVal ([a] -> WrappedVal [a]) -> Parser [a] -> Parser (WrappedVal [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [a]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
as
parseJSON Null = WrappedVal [a] -> Parser (WrappedVal [a])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WrappedVal [a] -> Parser (WrappedVal [a]))
-> WrappedVal [a] -> Parser (WrappedVal [a])
forall a b. (a -> b) -> a -> b
$ [a] -> WrappedVal [a]
forall a. a -> WrappedVal a
WrappedVal []
parseJSON _ = String -> Parser (WrappedVal [a])
forall (m :: * -> *) a. MonadFail m => String -> m a
fail "WrappedVal for List must be Array or Null"
data Timestamp =
Timestamp DiffTime deriving (Timestamp -> Timestamp -> Bool
(Timestamp -> Timestamp -> Bool)
-> (Timestamp -> Timestamp -> Bool) -> Eq Timestamp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Timestamp -> Timestamp -> Bool
$c/= :: Timestamp -> Timestamp -> Bool
== :: Timestamp -> Timestamp -> Bool
$c== :: Timestamp -> Timestamp -> Bool
Eq, Int -> Timestamp -> ShowS
[Timestamp] -> ShowS
Timestamp -> String
(Int -> Timestamp -> ShowS)
-> (Timestamp -> String)
-> ([Timestamp] -> ShowS)
-> Show Timestamp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Timestamp] -> ShowS
$cshowList :: [Timestamp] -> ShowS
show :: Timestamp -> String
$cshow :: Timestamp -> String
showsPrec :: Int -> Timestamp -> ShowS
$cshowsPrec :: Int -> Timestamp -> ShowS
Show, (forall x. Timestamp -> Rep Timestamp x)
-> (forall x. Rep Timestamp x -> Timestamp) -> Generic Timestamp
forall x. Rep Timestamp x -> Timestamp
forall x. Timestamp -> Rep Timestamp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Timestamp x -> Timestamp
$cfrom :: forall x. Timestamp -> Rep Timestamp x
Generic)
mkTimestamp :: DiffTime -> Timestamp
mkTimestamp :: DiffTime -> Timestamp
mkTimestamp ts :: DiffTime
ts =
let
ps :: Integer
ps = DiffTime -> Integer
diffTimeToPicoseconds DiffTime
ts
tenToThird :: Integer
tenToThird = 1000
nsResolution :: Integer
nsResolution = (Integer
ps Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
tenToThird) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
tenToThird
in
DiffTime -> Timestamp
Timestamp (DiffTime -> Timestamp) -> DiffTime -> Timestamp
forall a b. (a -> b) -> a -> b
$ Integer -> DiffTime
picosecondsToDiffTime Integer
nsResolution
instance ToJSON Timestamp
parseDiffTimeOrError :: String -> DiffTime
parseDiffTimeOrError :: String -> DiffTime
parseDiffTimeOrError = Bool -> TimeLocale -> String -> String -> DiffTime
forall t.
ParseTime t =>
Bool -> TimeLocale -> String -> String -> t
parseTimeOrError Bool
True TimeLocale
defaultTimeLocale "%FT%T%QZ"
instance FromJSON Timestamp where
parseJSON :: Value -> Parser Timestamp
parseJSON (String t :: Text
t) = Timestamp -> Parser Timestamp
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Timestamp -> Parser Timestamp)
-> (Text -> Timestamp) -> Text -> Parser Timestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiffTime -> Timestamp
mkTimestamp (DiffTime -> Timestamp) -> (Text -> DiffTime) -> Text -> Timestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> DiffTime
parseDiffTimeOrError (String -> DiffTime) -> (Text -> String) -> Text -> DiffTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> Parser Timestamp) -> Text -> Parser Timestamp
forall a b. (a -> b) -> a -> b
$ Text
t
parseJSON a :: Value
a = DiffTime -> Timestamp
mkTimestamp (DiffTime -> Timestamp)
-> (String -> DiffTime) -> String -> Timestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> DiffTime
parseDiffTimeOrError (String -> Timestamp) -> Parser String -> Parser Timestamp
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser String
forall a. FromJSON a => Value -> Parser a
parseJSON Value
a
instance Wrapped Timestamp where
type Unwrapped Timestamp = T.Timestamp
_Wrapped' :: p (Unwrapped Timestamp) (f (Unwrapped Timestamp))
-> p Timestamp (f Timestamp)
_Wrapped' = (Timestamp -> Timestamp)
-> (Timestamp -> Timestamp)
-> Iso Timestamp Timestamp Timestamp Timestamp
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Timestamp -> Timestamp
t Timestamp -> Timestamp
f
where
tenToTwelth :: Integer
tenToTwelth = 1000000000000
tenToThird :: Integer
tenToThird = 1000
t :: Timestamp -> Timestamp
t (Timestamp ts :: DiffTime
ts) =
let
ps :: Integer
ps = DiffTime -> Integer
diffTimeToPicoseconds DiffTime
ts
s :: Integer
s = Integer
ps Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
tenToTwelth
ns :: Integer
ns = (Integer
ps Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
s Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
tenToTwelth) Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
tenToThird
in
Timestamp
forall msg. Message msg => msg
defMessage Timestamp -> (Timestamp -> Timestamp) -> Timestamp
forall a b. a -> (a -> b) -> b
& LensLike' Identity Timestamp Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "seconds" a) =>
LensLike' f s a
T.seconds LensLike' Identity Timestamp Int64
-> Int64 -> Timestamp -> Timestamp
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Integer -> Int64
forall a. Num a => Integer -> a
fromInteger Integer
s
Timestamp -> (Timestamp -> Timestamp) -> Timestamp
forall a b. a -> (a -> b) -> b
& LensLike' Identity Timestamp Int32
forall (f :: * -> *) s a.
(Functor f, HasField s "nanos" a) =>
LensLike' f s a
T.nanos LensLike' Identity Timestamp Int32
-> Int32 -> Timestamp -> Timestamp
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Integer -> Int32
forall a. Num a => Integer -> a
fromInteger Integer
ns
f :: Timestamp -> Timestamp
f ts :: Timestamp
ts =
let
ps1 :: Integer
ps1 = Int64 -> Integer
forall a. Integral a => a -> Integer
toInteger (Timestamp
ts Timestamp -> Getting Int64 Timestamp Int64 -> Int64
forall s a. s -> Getting a s a -> a
^. Getting Int64 Timestamp Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "seconds" a) =>
LensLike' f s a
T.seconds) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
tenToTwelth
ps2 :: Integer
ps2 = Int32 -> Integer
forall a. Integral a => a -> Integer
toInteger (Timestamp
ts Timestamp -> Getting Int32 Timestamp Int32 -> Int32
forall s a. s -> Getting a s a -> a
^. Getting Int32 Timestamp Int32
forall (f :: * -> *) s a.
(Functor f, HasField s "nanos" a) =>
LensLike' f s a
T.nanos) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
tenToThird
in
DiffTime -> Timestamp
mkTimestamp (DiffTime -> Timestamp)
-> (Integer -> DiffTime) -> Integer -> Timestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> DiffTime
picosecondsToDiffTime (Integer -> Timestamp) -> Integer -> Timestamp
forall a b. (a -> b) -> a -> b
$ Integer
ps1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
ps2
data BlockParams = BlockParams
{ BlockParams -> WrappedVal Int64
blockParamsMaxBytes :: WrappedVal Int64
, BlockParams -> WrappedVal Int64
blockParamsMaxGas :: WrappedVal Int64
} deriving (BlockParams -> BlockParams -> Bool
(BlockParams -> BlockParams -> Bool)
-> (BlockParams -> BlockParams -> Bool) -> Eq BlockParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockParams -> BlockParams -> Bool
$c/= :: BlockParams -> BlockParams -> Bool
== :: BlockParams -> BlockParams -> Bool
$c== :: BlockParams -> BlockParams -> Bool
Eq, Int -> BlockParams -> ShowS
[BlockParams] -> ShowS
BlockParams -> String
(Int -> BlockParams -> ShowS)
-> (BlockParams -> String)
-> ([BlockParams] -> ShowS)
-> Show BlockParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockParams] -> ShowS
$cshowList :: [BlockParams] -> ShowS
show :: BlockParams -> String
$cshow :: BlockParams -> String
showsPrec :: Int -> BlockParams -> ShowS
$cshowsPrec :: Int -> BlockParams -> ShowS
Show, (forall x. BlockParams -> Rep BlockParams x)
-> (forall x. Rep BlockParams x -> BlockParams)
-> Generic BlockParams
forall x. Rep BlockParams x -> BlockParams
forall x. BlockParams -> Rep BlockParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlockParams x -> BlockParams
$cfrom :: forall x. BlockParams -> Rep BlockParams x
Generic)
instance ToJSON BlockParams where
toJSON :: BlockParams -> Value
toJSON = Options -> BlockParams -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> BlockParams -> Value)
-> Options -> BlockParams -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "blockParams"
instance FromJSON BlockParams where
parseJSON :: Value -> Parser BlockParams
parseJSON = Options -> Value -> Parser BlockParams
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser BlockParams)
-> Options -> Value -> Parser BlockParams
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "blockParams"
instance Wrapped BlockParams where
type Unwrapped BlockParams = PT.BlockParams
_Wrapped' :: p (Unwrapped BlockParams) (f (Unwrapped BlockParams))
-> p BlockParams (f BlockParams)
_Wrapped' = (BlockParams -> BlockParams)
-> (BlockParams -> BlockParams)
-> Iso BlockParams BlockParams BlockParams BlockParams
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso BlockParams -> BlockParams
forall b.
(Message b, HasField b "maxBytes" Int64,
HasField b "maxGas" Int64) =>
BlockParams -> b
t BlockParams -> BlockParams
forall s.
(HasField s "maxBytes" Int64, HasField s "maxGas" Int64) =>
s -> BlockParams
f
where
t :: BlockParams -> b
t BlockParams{..} =
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 "maxBytes" a) =>
LensLike' f s a
PT.maxBytes 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
blockParamsMaxBytes
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "maxGas" a) =>
LensLike' f s a
PT.maxGas 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
blockParamsMaxGas
f :: s -> BlockParams
f a :: s
a =
BlockParams :: WrappedVal Int64 -> WrappedVal Int64 -> BlockParams
BlockParams
{ blockParamsMaxBytes :: WrappedVal Int64
blockParamsMaxBytes = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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 "maxBytes" a) =>
LensLike' f s a
PT.maxBytes
, blockParamsMaxGas :: WrappedVal Int64
blockParamsMaxGas = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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 "maxGas" a) =>
LensLike' f s a
PT.maxGas
}
data EvidenceParams = EvidenceParams
{ EvidenceParams -> WrappedVal Int64
evidenceParamsMaxAge :: WrappedVal Int64
} deriving (EvidenceParams -> EvidenceParams -> Bool
(EvidenceParams -> EvidenceParams -> Bool)
-> (EvidenceParams -> EvidenceParams -> Bool) -> Eq EvidenceParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EvidenceParams -> EvidenceParams -> Bool
$c/= :: EvidenceParams -> EvidenceParams -> Bool
== :: EvidenceParams -> EvidenceParams -> Bool
$c== :: EvidenceParams -> EvidenceParams -> Bool
Eq, Int -> EvidenceParams -> ShowS
[EvidenceParams] -> ShowS
EvidenceParams -> String
(Int -> EvidenceParams -> ShowS)
-> (EvidenceParams -> String)
-> ([EvidenceParams] -> ShowS)
-> Show EvidenceParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EvidenceParams] -> ShowS
$cshowList :: [EvidenceParams] -> ShowS
show :: EvidenceParams -> String
$cshow :: EvidenceParams -> String
showsPrec :: Int -> EvidenceParams -> ShowS
$cshowsPrec :: Int -> EvidenceParams -> ShowS
Show, (forall x. EvidenceParams -> Rep EvidenceParams x)
-> (forall x. Rep EvidenceParams x -> EvidenceParams)
-> Generic EvidenceParams
forall x. Rep EvidenceParams x -> EvidenceParams
forall x. EvidenceParams -> Rep EvidenceParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EvidenceParams x -> EvidenceParams
$cfrom :: forall x. EvidenceParams -> Rep EvidenceParams x
Generic)
instance ToJSON EvidenceParams where
toJSON :: EvidenceParams -> Value
toJSON = Options -> EvidenceParams -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> EvidenceParams -> Value)
-> Options -> EvidenceParams -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "evidenceParams"
instance FromJSON EvidenceParams where
parseJSON :: Value -> Parser EvidenceParams
parseJSON = Options -> Value -> Parser EvidenceParams
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser EvidenceParams)
-> Options -> Value -> Parser EvidenceParams
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "evidenceParams"
instance Wrapped EvidenceParams where
type Unwrapped EvidenceParams = PT.EvidenceParams
_Wrapped' :: p (Unwrapped EvidenceParams) (f (Unwrapped EvidenceParams))
-> p EvidenceParams (f EvidenceParams)
_Wrapped' = (EvidenceParams -> EvidenceParams)
-> (EvidenceParams -> EvidenceParams)
-> Iso EvidenceParams EvidenceParams EvidenceParams EvidenceParams
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso EvidenceParams -> EvidenceParams
forall b.
(Message b, HasField b "maxAge" Int64) =>
EvidenceParams -> b
t EvidenceParams -> EvidenceParams
forall s. HasField s "maxAge" Int64 => s -> EvidenceParams
f
where
t :: EvidenceParams -> b
t EvidenceParams{..} =
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 "maxAge" a) =>
LensLike' f s a
PT.maxAge 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
evidenceParamsMaxAge
f :: s -> EvidenceParams
f a :: s
a =
EvidenceParams :: WrappedVal Int64 -> EvidenceParams
EvidenceParams
{ evidenceParamsMaxAge :: WrappedVal Int64
evidenceParamsMaxAge = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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 "maxAge" a) =>
LensLike' f s a
PT.maxAge
}
data ValidatorParams = ValidatorParams
{ ValidatorParams -> [Text]
validatorParamsPubKeyTypes :: [Text]
} deriving (ValidatorParams -> ValidatorParams -> Bool
(ValidatorParams -> ValidatorParams -> Bool)
-> (ValidatorParams -> ValidatorParams -> Bool)
-> Eq ValidatorParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidatorParams -> ValidatorParams -> Bool
$c/= :: ValidatorParams -> ValidatorParams -> Bool
== :: ValidatorParams -> ValidatorParams -> Bool
$c== :: ValidatorParams -> ValidatorParams -> Bool
Eq, Int -> ValidatorParams -> ShowS
[ValidatorParams] -> ShowS
ValidatorParams -> String
(Int -> ValidatorParams -> ShowS)
-> (ValidatorParams -> String)
-> ([ValidatorParams] -> ShowS)
-> Show ValidatorParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValidatorParams] -> ShowS
$cshowList :: [ValidatorParams] -> ShowS
show :: ValidatorParams -> String
$cshow :: ValidatorParams -> String
showsPrec :: Int -> ValidatorParams -> ShowS
$cshowsPrec :: Int -> ValidatorParams -> ShowS
Show, (forall x. ValidatorParams -> Rep ValidatorParams x)
-> (forall x. Rep ValidatorParams x -> ValidatorParams)
-> Generic ValidatorParams
forall x. Rep ValidatorParams x -> ValidatorParams
forall x. ValidatorParams -> Rep ValidatorParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ValidatorParams x -> ValidatorParams
$cfrom :: forall x. ValidatorParams -> Rep ValidatorParams x
Generic)
instance ToJSON ValidatorParams where
toJSON :: ValidatorParams -> Value
toJSON = Options -> ValidatorParams -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> ValidatorParams -> Value)
-> Options -> ValidatorParams -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "validatorParams"
instance FromJSON ValidatorParams where
parseJSON :: Value -> Parser ValidatorParams
parseJSON = String
-> (Object -> Parser ValidatorParams)
-> Value
-> Parser ValidatorParams
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject "ValidatorParams" ((Object -> Parser ValidatorParams)
-> Value -> Parser ValidatorParams)
-> (Object -> Parser ValidatorParams)
-> Value
-> Parser ValidatorParams
forall a b. (a -> b) -> a -> b
$ \v :: Object
v -> [Text] -> ValidatorParams
ValidatorParams
([Text] -> ValidatorParams)
-> Parser [Text] -> Parser ValidatorParams
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "pubKeyTypes" Parser (Maybe [Text]) -> [Text] -> Parser [Text]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
instance Wrapped ValidatorParams where
type Unwrapped ValidatorParams = PT.ValidatorParams
_Wrapped' :: p (Unwrapped ValidatorParams) (f (Unwrapped ValidatorParams))
-> p ValidatorParams (f ValidatorParams)
_Wrapped' = (ValidatorParams -> ValidatorParams)
-> (ValidatorParams -> ValidatorParams)
-> Iso
ValidatorParams ValidatorParams ValidatorParams ValidatorParams
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ValidatorParams -> ValidatorParams
forall b.
(Message b, HasField b "pubKeyTypes" [Text]) =>
ValidatorParams -> b
t ValidatorParams -> ValidatorParams
forall s. HasField s "pubKeyTypes" [Text] => s -> ValidatorParams
f
where
t :: ValidatorParams -> b
t ValidatorParams{..} =
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 "pubKeyTypes" a) =>
LensLike' f s a
PT.pubKeyTypes LensLike' Identity b [Text] -> [Text] -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Text]
validatorParamsPubKeyTypes
f :: s -> ValidatorParams
f a :: s
a =
ValidatorParams :: [Text] -> ValidatorParams
ValidatorParams
{ validatorParamsPubKeyTypes :: [Text]
validatorParamsPubKeyTypes = s
a 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 "pubKeyTypes" a) =>
LensLike' f s a
PT.pubKeyTypes
}
data ConsensusParams = ConsensusParams
{ ConsensusParams -> Maybe BlockParams
consensusParamsBlockSize :: Maybe BlockParams
, ConsensusParams -> Maybe EvidenceParams
consensusParamsEvidence :: Maybe EvidenceParams
, ConsensusParams -> Maybe ValidatorParams
consensusParamsValidator :: Maybe ValidatorParams
} deriving (ConsensusParams -> ConsensusParams -> Bool
(ConsensusParams -> ConsensusParams -> Bool)
-> (ConsensusParams -> ConsensusParams -> Bool)
-> Eq ConsensusParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConsensusParams -> ConsensusParams -> Bool
$c/= :: ConsensusParams -> ConsensusParams -> Bool
== :: ConsensusParams -> ConsensusParams -> Bool
$c== :: ConsensusParams -> ConsensusParams -> Bool
Eq, Int -> ConsensusParams -> ShowS
[ConsensusParams] -> ShowS
ConsensusParams -> String
(Int -> ConsensusParams -> ShowS)
-> (ConsensusParams -> String)
-> ([ConsensusParams] -> ShowS)
-> Show ConsensusParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConsensusParams] -> ShowS
$cshowList :: [ConsensusParams] -> ShowS
show :: ConsensusParams -> String
$cshow :: ConsensusParams -> String
showsPrec :: Int -> ConsensusParams -> ShowS
$cshowsPrec :: Int -> ConsensusParams -> ShowS
Show, (forall x. ConsensusParams -> Rep ConsensusParams x)
-> (forall x. Rep ConsensusParams x -> ConsensusParams)
-> Generic ConsensusParams
forall x. Rep ConsensusParams x -> ConsensusParams
forall x. ConsensusParams -> Rep ConsensusParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConsensusParams x -> ConsensusParams
$cfrom :: forall x. ConsensusParams -> Rep ConsensusParams x
Generic)
instance ToJSON ConsensusParams where
toJSON :: ConsensusParams -> Value
toJSON = Options -> ConsensusParams -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> ConsensusParams -> Value)
-> Options -> ConsensusParams -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "consensusParams"
instance FromJSON ConsensusParams where
parseJSON :: Value -> Parser ConsensusParams
parseJSON = Options -> Value -> Parser ConsensusParams
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser ConsensusParams)
-> Options -> Value -> Parser ConsensusParams
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "consensusParams"
instance Wrapped ConsensusParams where
type Unwrapped ConsensusParams = PT.ConsensusParams
_Wrapped' :: p (Unwrapped ConsensusParams) (f (Unwrapped ConsensusParams))
-> p ConsensusParams (f ConsensusParams)
_Wrapped' = (ConsensusParams -> ConsensusParams)
-> (ConsensusParams -> ConsensusParams)
-> Iso
ConsensusParams ConsensusParams ConsensusParams ConsensusParams
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ConsensusParams -> ConsensusParams
forall b.
(Message b, HasField b "maybe'block" (Maybe BlockParams),
HasField b "maybe'evidence" (Maybe EvidenceParams),
HasField b "maybe'validator" (Maybe ValidatorParams)) =>
ConsensusParams -> b
t ConsensusParams -> ConsensusParams
forall s.
(HasField s "maybe'block" (Maybe BlockParams),
HasField s "maybe'evidence" (Maybe EvidenceParams),
HasField s "maybe'validator" (Maybe ValidatorParams)) =>
s -> ConsensusParams
f
where
t :: ConsensusParams -> b
t ConsensusParams{..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe BlockParams)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'block" a) =>
LensLike' f s a
PT.maybe'block LensLike' Identity b (Maybe BlockParams)
-> Maybe BlockParams -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe BlockParams
consensusParamsBlockSize Maybe BlockParams
-> Getting (First BlockParams) (Maybe BlockParams) BlockParams
-> Maybe BlockParams
forall s a. s -> Getting (First a) s a -> Maybe a
^? (BlockParams -> Const (First BlockParams) BlockParams)
-> Maybe BlockParams
-> Const (First BlockParams) (Maybe BlockParams)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((BlockParams -> Const (First BlockParams) BlockParams)
-> Maybe BlockParams
-> Const (First BlockParams) (Maybe BlockParams))
-> ((BlockParams -> Const (First BlockParams) BlockParams)
-> BlockParams -> Const (First BlockParams) BlockParams)
-> Getting (First BlockParams) (Maybe BlockParams) BlockParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BlockParams -> Const (First BlockParams) BlockParams)
-> BlockParams -> Const (First BlockParams) BlockParams
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe EvidenceParams)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'evidence" a) =>
LensLike' f s a
PT.maybe'evidence LensLike' Identity b (Maybe EvidenceParams)
-> Maybe EvidenceParams -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe EvidenceParams
consensusParamsEvidence Maybe EvidenceParams
-> Getting
(First EvidenceParams) (Maybe EvidenceParams) EvidenceParams
-> Maybe EvidenceParams
forall s a. s -> Getting (First a) s a -> Maybe a
^? (EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> Maybe EvidenceParams
-> Const (First EvidenceParams) (Maybe EvidenceParams)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> Maybe EvidenceParams
-> Const (First EvidenceParams) (Maybe EvidenceParams))
-> ((EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> Getting
(First EvidenceParams) (Maybe EvidenceParams) EvidenceParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> EvidenceParams -> Const (First EvidenceParams) EvidenceParams
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe ValidatorParams)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'validator" a) =>
LensLike' f s a
PT.maybe'validator LensLike' Identity b (Maybe ValidatorParams)
-> Maybe ValidatorParams -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe ValidatorParams
consensusParamsValidator Maybe ValidatorParams
-> Getting
(First ValidatorParams) (Maybe ValidatorParams) ValidatorParams
-> Maybe ValidatorParams
forall s a. s -> Getting (First a) s a -> Maybe a
^? (ValidatorParams -> Const (First ValidatorParams) ValidatorParams)
-> Maybe ValidatorParams
-> Const (First ValidatorParams) (Maybe ValidatorParams)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((ValidatorParams -> Const (First ValidatorParams) ValidatorParams)
-> Maybe ValidatorParams
-> Const (First ValidatorParams) (Maybe ValidatorParams))
-> ((ValidatorParams
-> Const (First ValidatorParams) ValidatorParams)
-> ValidatorParams
-> Const (First ValidatorParams) ValidatorParams)
-> Getting
(First ValidatorParams) (Maybe ValidatorParams) ValidatorParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ValidatorParams -> Const (First ValidatorParams) ValidatorParams)
-> ValidatorParams -> Const (First ValidatorParams) ValidatorParams
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
f :: s -> ConsensusParams
f a :: s
a =
ConsensusParams :: Maybe BlockParams
-> Maybe EvidenceParams -> Maybe ValidatorParams -> ConsensusParams
ConsensusParams
{ consensusParamsBlockSize :: Maybe BlockParams
consensusParamsBlockSize = s
a s -> Getting (First BlockParams) s BlockParams -> Maybe BlockParams
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First BlockParams)) s (Maybe BlockParams)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'block" a) =>
LensLike' f s a
PT.maybe'block LensLike' (Const (First BlockParams)) s (Maybe BlockParams)
-> ((BlockParams -> Const (First BlockParams) BlockParams)
-> Maybe BlockParams
-> Const (First BlockParams) (Maybe BlockParams))
-> Getting (First BlockParams) s BlockParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BlockParams -> Const (First BlockParams) BlockParams)
-> Maybe BlockParams
-> Const (First BlockParams) (Maybe BlockParams)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((BlockParams -> Const (First BlockParams) BlockParams)
-> Maybe BlockParams
-> Const (First BlockParams) (Maybe BlockParams))
-> ((BlockParams -> Const (First BlockParams) BlockParams)
-> BlockParams -> Const (First BlockParams) BlockParams)
-> (BlockParams -> Const (First BlockParams) BlockParams)
-> Maybe BlockParams
-> Const (First BlockParams) (Maybe BlockParams)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BlockParams -> Const (First BlockParams) BlockParams)
-> BlockParams -> Const (First BlockParams) BlockParams
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, consensusParamsEvidence :: Maybe EvidenceParams
consensusParamsEvidence = s
a s
-> Getting (First EvidenceParams) s EvidenceParams
-> Maybe EvidenceParams
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First EvidenceParams)) s (Maybe EvidenceParams)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'evidence" a) =>
LensLike' f s a
PT.maybe'evidence LensLike' (Const (First EvidenceParams)) s (Maybe EvidenceParams)
-> ((EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> Maybe EvidenceParams
-> Const (First EvidenceParams) (Maybe EvidenceParams))
-> Getting (First EvidenceParams) s EvidenceParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> Maybe EvidenceParams
-> Const (First EvidenceParams) (Maybe EvidenceParams)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> Maybe EvidenceParams
-> Const (First EvidenceParams) (Maybe EvidenceParams))
-> ((EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> (EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> Maybe EvidenceParams
-> Const (First EvidenceParams) (Maybe EvidenceParams)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (EvidenceParams -> Const (First EvidenceParams) EvidenceParams)
-> EvidenceParams -> Const (First EvidenceParams) EvidenceParams
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, consensusParamsValidator :: Maybe ValidatorParams
consensusParamsValidator = s
a s
-> Getting (First ValidatorParams) s ValidatorParams
-> Maybe ValidatorParams
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First ValidatorParams)) s (Maybe ValidatorParams)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'validator" a) =>
LensLike' f s a
PT.maybe'validator LensLike' (Const (First ValidatorParams)) s (Maybe ValidatorParams)
-> ((ValidatorParams
-> Const (First ValidatorParams) ValidatorParams)
-> Maybe ValidatorParams
-> Const (First ValidatorParams) (Maybe ValidatorParams))
-> Getting (First ValidatorParams) s ValidatorParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ValidatorParams -> Const (First ValidatorParams) ValidatorParams)
-> Maybe ValidatorParams
-> Const (First ValidatorParams) (Maybe ValidatorParams)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((ValidatorParams -> Const (First ValidatorParams) ValidatorParams)
-> Maybe ValidatorParams
-> Const (First ValidatorParams) (Maybe ValidatorParams))
-> ((ValidatorParams
-> Const (First ValidatorParams) ValidatorParams)
-> ValidatorParams
-> Const (First ValidatorParams) ValidatorParams)
-> (ValidatorParams
-> Const (First ValidatorParams) ValidatorParams)
-> Maybe ValidatorParams
-> Const (First ValidatorParams) (Maybe ValidatorParams)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ValidatorParams -> Const (First ValidatorParams) ValidatorParams)
-> ValidatorParams -> Const (First ValidatorParams) ValidatorParams
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
}
data PubKey = PubKey
{ PubKey -> Text
pubKeyType :: Text
, PubKey -> Base64String
pubKeyData :: Base64String
} deriving (PubKey -> PubKey -> Bool
(PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> Bool) -> Eq PubKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PubKey -> PubKey -> Bool
$c/= :: PubKey -> PubKey -> Bool
== :: PubKey -> PubKey -> Bool
$c== :: PubKey -> PubKey -> Bool
Eq, Eq PubKey
Eq PubKey =>
(PubKey -> PubKey -> Ordering)
-> (PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> PubKey)
-> (PubKey -> PubKey -> PubKey)
-> Ord PubKey
PubKey -> PubKey -> Bool
PubKey -> PubKey -> Ordering
PubKey -> PubKey -> PubKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PubKey -> PubKey -> PubKey
$cmin :: PubKey -> PubKey -> PubKey
max :: PubKey -> PubKey -> PubKey
$cmax :: PubKey -> PubKey -> PubKey
>= :: PubKey -> PubKey -> Bool
$c>= :: PubKey -> PubKey -> Bool
> :: PubKey -> PubKey -> Bool
$c> :: PubKey -> PubKey -> Bool
<= :: PubKey -> PubKey -> Bool
$c<= :: PubKey -> PubKey -> Bool
< :: PubKey -> PubKey -> Bool
$c< :: PubKey -> PubKey -> Bool
compare :: PubKey -> PubKey -> Ordering
$ccompare :: PubKey -> PubKey -> Ordering
$cp1Ord :: Eq PubKey
Ord, Int -> PubKey -> ShowS
[PubKey] -> ShowS
PubKey -> String
(Int -> PubKey -> ShowS)
-> (PubKey -> String) -> ([PubKey] -> ShowS) -> Show PubKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PubKey] -> ShowS
$cshowList :: [PubKey] -> ShowS
show :: PubKey -> String
$cshow :: PubKey -> String
showsPrec :: Int -> PubKey -> ShowS
$cshowsPrec :: Int -> PubKey -> ShowS
Show, (forall x. PubKey -> Rep PubKey x)
-> (forall x. Rep PubKey x -> PubKey) -> Generic PubKey
forall x. Rep PubKey x -> PubKey
forall x. PubKey -> Rep PubKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PubKey x -> PubKey
$cfrom :: forall x. PubKey -> Rep PubKey x
Generic)
instance ToJSON PubKey where
toJSON :: PubKey -> Value
toJSON = Options -> PubKey -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> PubKey -> Value) -> Options -> PubKey -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "pubKey"
instance FromJSON PubKey where
parseJSON :: Value -> Parser PubKey
parseJSON = Options -> Value -> Parser PubKey
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser PubKey)
-> Options -> Value -> Parser PubKey
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "pubKey"
instance Wrapped PubKey where
type Unwrapped PubKey = PT.PubKey
_Wrapped' :: p (Unwrapped PubKey) (f (Unwrapped PubKey)) -> p PubKey (f PubKey)
_Wrapped' = (PubKey -> PubKey)
-> (PubKey -> PubKey) -> Iso PubKey PubKey PubKey PubKey
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso PubKey -> PubKey
forall b a.
(Message b, HasField b "data'" a, HasField b "type'" Text,
ByteArray a) =>
PubKey -> b
t PubKey -> PubKey
forall ba s.
(ByteArrayAccess ba, HasField s "data'" ba,
HasField s "type'" Text) =>
s -> PubKey
f
where
t :: PubKey -> b
t PubKey{..} =
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 "type'" a) =>
LensLike' f s a
PT.type' LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
pubKeyType
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
pubKeyData
f :: s -> PubKey
f a :: s
a =
PubKey :: Text -> Base64String -> PubKey
PubKey
{ pubKeyType :: Text
pubKeyType = s
a 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 "type'" a) =>
LensLike' f s a
PT.type'
, pubKeyData :: Base64String
pubKeyData = ba -> Base64String
forall ba. ByteArrayAccess ba => ba -> Base64String
Base64.fromBytes (s
a 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')
}
data ValidatorUpdate = ValidatorUpdate
{ ValidatorUpdate -> Maybe PubKey
validatorUpdatePubKey :: Maybe PubKey
, ValidatorUpdate -> WrappedVal Int64
validatorUpdatePower :: WrappedVal Int64
} deriving (ValidatorUpdate -> ValidatorUpdate -> Bool
(ValidatorUpdate -> ValidatorUpdate -> Bool)
-> (ValidatorUpdate -> ValidatorUpdate -> Bool)
-> Eq ValidatorUpdate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidatorUpdate -> ValidatorUpdate -> Bool
$c/= :: ValidatorUpdate -> ValidatorUpdate -> Bool
== :: ValidatorUpdate -> ValidatorUpdate -> Bool
$c== :: ValidatorUpdate -> ValidatorUpdate -> Bool
Eq, Int -> ValidatorUpdate -> ShowS
[ValidatorUpdate] -> ShowS
ValidatorUpdate -> String
(Int -> ValidatorUpdate -> ShowS)
-> (ValidatorUpdate -> String)
-> ([ValidatorUpdate] -> ShowS)
-> Show ValidatorUpdate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValidatorUpdate] -> ShowS
$cshowList :: [ValidatorUpdate] -> ShowS
show :: ValidatorUpdate -> String
$cshow :: ValidatorUpdate -> String
showsPrec :: Int -> ValidatorUpdate -> ShowS
$cshowsPrec :: Int -> ValidatorUpdate -> ShowS
Show, (forall x. ValidatorUpdate -> Rep ValidatorUpdate x)
-> (forall x. Rep ValidatorUpdate x -> ValidatorUpdate)
-> Generic ValidatorUpdate
forall x. Rep ValidatorUpdate x -> ValidatorUpdate
forall x. ValidatorUpdate -> Rep ValidatorUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ValidatorUpdate x -> ValidatorUpdate
$cfrom :: forall x. ValidatorUpdate -> Rep ValidatorUpdate x
Generic)
instance ToJSON ValidatorUpdate where
toJSON :: ValidatorUpdate -> Value
toJSON = Options -> ValidatorUpdate -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> ValidatorUpdate -> Value)
-> Options -> ValidatorUpdate -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "validatorUpdate"
instance FromJSON ValidatorUpdate where
parseJSON :: Value -> Parser ValidatorUpdate
parseJSON = Options -> Value -> Parser ValidatorUpdate
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser ValidatorUpdate)
-> Options -> Value -> Parser ValidatorUpdate
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "validatorUpdate"
instance Wrapped ValidatorUpdate where
type Unwrapped ValidatorUpdate = PT.ValidatorUpdate
_Wrapped' :: p (Unwrapped ValidatorUpdate) (f (Unwrapped ValidatorUpdate))
-> p ValidatorUpdate (f ValidatorUpdate)
_Wrapped' = (ValidatorUpdate -> ValidatorUpdate)
-> (ValidatorUpdate -> ValidatorUpdate)
-> Iso
ValidatorUpdate ValidatorUpdate ValidatorUpdate ValidatorUpdate
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ValidatorUpdate -> ValidatorUpdate
forall b.
(Message b, HasField b "maybe'pubKey" (Maybe PubKey),
HasField b "power" Int64) =>
ValidatorUpdate -> b
t ValidatorUpdate -> ValidatorUpdate
forall s.
(HasField s "maybe'pubKey" (Maybe PubKey),
HasField s "power" Int64) =>
s -> ValidatorUpdate
f
where
t :: ValidatorUpdate -> b
t ValidatorUpdate{..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe PubKey)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'pubKey" a) =>
LensLike' f s a
PT.maybe'pubKey LensLike' Identity b (Maybe PubKey) -> Maybe PubKey -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe PubKey
validatorUpdatePubKey Maybe PubKey
-> Getting (First PubKey) (Maybe PubKey) PubKey -> Maybe PubKey
forall s a. s -> Getting (First a) s a -> Maybe a
^? (PubKey -> Const (First PubKey) PubKey)
-> Maybe PubKey -> Const (First PubKey) (Maybe PubKey)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((PubKey -> Const (First PubKey) PubKey)
-> Maybe PubKey -> Const (First PubKey) (Maybe PubKey))
-> ((PubKey -> Const (First PubKey) PubKey)
-> PubKey -> Const (First PubKey) PubKey)
-> Getting (First PubKey) (Maybe PubKey) PubKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PubKey -> Const (First PubKey) PubKey)
-> PubKey -> Const (First PubKey) PubKey
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "power" a) =>
LensLike' f s a
PT.power 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
validatorUpdatePower
f :: s -> ValidatorUpdate
f a :: s
a =
ValidatorUpdate :: Maybe PubKey -> WrappedVal Int64 -> ValidatorUpdate
ValidatorUpdate
{ validatorUpdatePubKey :: Maybe PubKey
validatorUpdatePubKey = s
a s -> Getting (First PubKey) s PubKey -> Maybe PubKey
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First PubKey)) s (Maybe PubKey)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'pubKey" a) =>
LensLike' f s a
PT.maybe'pubKey LensLike' (Const (First PubKey)) s (Maybe PubKey)
-> ((PubKey -> Const (First PubKey) PubKey)
-> Maybe PubKey -> Const (First PubKey) (Maybe PubKey))
-> Getting (First PubKey) s PubKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PubKey -> Const (First PubKey) PubKey)
-> Maybe PubKey -> Const (First PubKey) (Maybe PubKey)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((PubKey -> Const (First PubKey) PubKey)
-> Maybe PubKey -> Const (First PubKey) (Maybe PubKey))
-> ((PubKey -> Const (First PubKey) PubKey)
-> PubKey -> Const (First PubKey) PubKey)
-> (PubKey -> Const (First PubKey) PubKey)
-> Maybe PubKey
-> Const (First PubKey) (Maybe PubKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PubKey -> Const (First PubKey) PubKey)
-> PubKey -> Const (First PubKey) PubKey
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, validatorUpdatePower :: WrappedVal Int64
validatorUpdatePower = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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 "power" a) =>
LensLike' f s a
PT.power
}
data Validator = Validator
{ Validator -> HexString
validatorAddress :: HexString
, Validator -> WrappedVal Int64
validatorPower :: WrappedVal Int64
} deriving (Validator -> Validator -> Bool
(Validator -> Validator -> Bool)
-> (Validator -> Validator -> Bool) -> Eq Validator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Validator -> Validator -> Bool
$c/= :: Validator -> Validator -> Bool
== :: Validator -> Validator -> Bool
$c== :: Validator -> Validator -> Bool
Eq, Int -> Validator -> ShowS
[Validator] -> ShowS
Validator -> String
(Int -> Validator -> ShowS)
-> (Validator -> String)
-> ([Validator] -> ShowS)
-> Show Validator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Validator] -> ShowS
$cshowList :: [Validator] -> ShowS
show :: Validator -> String
$cshow :: Validator -> String
showsPrec :: Int -> Validator -> ShowS
$cshowsPrec :: Int -> Validator -> ShowS
Show, (forall x. Validator -> Rep Validator x)
-> (forall x. Rep Validator x -> Validator) -> Generic Validator
forall x. Rep Validator x -> Validator
forall x. Validator -> Rep Validator x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Validator x -> Validator
$cfrom :: forall x. Validator -> Rep Validator x
Generic)
instance ToJSON Validator where
toJSON :: Validator -> Value
toJSON = Options -> Validator -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Validator -> Value) -> Options -> Validator -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "validator"
instance FromJSON Validator where
parseJSON :: Value -> Parser Validator
parseJSON = Options -> Value -> Parser Validator
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Validator)
-> Options -> Value -> Parser Validator
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "validator"
instance Wrapped Validator where
type Unwrapped Validator = PT.Validator
_Wrapped' :: p (Unwrapped Validator) (f (Unwrapped Validator))
-> p Validator (f Validator)
_Wrapped' = (Validator -> Validator)
-> (Validator -> Validator)
-> Iso Validator Validator Validator Validator
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Validator -> Validator
forall b a.
(Message b, ByteArray a, HasField b "address" a,
HasField b "power" Int64) =>
Validator -> b
t Validator -> Validator
forall ba s.
(ByteArrayAccess ba, HasField s "address" ba,
HasField s "power" Int64) =>
s -> Validator
f
where
t :: Validator -> b
t Validator{..} =
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 "address" a) =>
LensLike' f s a
PT.address 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
validatorAddress
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "power" a) =>
LensLike' f s a
PT.power 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
validatorPower
f :: s -> Validator
f a :: s
a =
Validator :: HexString -> WrappedVal Int64 -> Validator
Validator
{ validatorAddress :: HexString
validatorAddress = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (s
a 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 "address" a) =>
LensLike' f s a
PT.address)
, validatorPower :: WrappedVal Int64
validatorPower = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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 "power" a) =>
LensLike' f s a
PT.power
}
data VoteInfo = VoteInfo
{ VoteInfo -> Maybe Validator
voteInfoValidator :: Maybe Validator
, VoteInfo -> Bool
voteInfoSignedLastBlock :: Bool
} deriving (VoteInfo -> VoteInfo -> Bool
(VoteInfo -> VoteInfo -> Bool)
-> (VoteInfo -> VoteInfo -> Bool) -> Eq VoteInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VoteInfo -> VoteInfo -> Bool
$c/= :: VoteInfo -> VoteInfo -> Bool
== :: VoteInfo -> VoteInfo -> Bool
$c== :: VoteInfo -> VoteInfo -> Bool
Eq, Int -> VoteInfo -> ShowS
[VoteInfo] -> ShowS
VoteInfo -> String
(Int -> VoteInfo -> ShowS)
-> (VoteInfo -> String) -> ([VoteInfo] -> ShowS) -> Show VoteInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VoteInfo] -> ShowS
$cshowList :: [VoteInfo] -> ShowS
show :: VoteInfo -> String
$cshow :: VoteInfo -> String
showsPrec :: Int -> VoteInfo -> ShowS
$cshowsPrec :: Int -> VoteInfo -> ShowS
Show, (forall x. VoteInfo -> Rep VoteInfo x)
-> (forall x. Rep VoteInfo x -> VoteInfo) -> Generic VoteInfo
forall x. Rep VoteInfo x -> VoteInfo
forall x. VoteInfo -> Rep VoteInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VoteInfo x -> VoteInfo
$cfrom :: forall x. VoteInfo -> Rep VoteInfo x
Generic)
instance ToJSON VoteInfo where
toJSON :: VoteInfo -> Value
toJSON = Options -> VoteInfo -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> VoteInfo -> Value) -> Options -> VoteInfo -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "voteInfo"
instance FromJSON VoteInfo where
parseJSON :: Value -> Parser VoteInfo
parseJSON = Options -> Value -> Parser VoteInfo
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser VoteInfo)
-> Options -> Value -> Parser VoteInfo
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "voteInfo"
instance Wrapped VoteInfo where
type Unwrapped VoteInfo = PT.VoteInfo
_Wrapped' :: p (Unwrapped VoteInfo) (f (Unwrapped VoteInfo))
-> p VoteInfo (f VoteInfo)
_Wrapped' = (VoteInfo -> VoteInfo)
-> (VoteInfo -> VoteInfo)
-> Iso VoteInfo VoteInfo VoteInfo VoteInfo
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso VoteInfo -> VoteInfo
forall b.
(Message b, HasField b "maybe'validator" (Maybe Validator),
HasField b "signedLastBlock" Bool) =>
VoteInfo -> b
t VoteInfo -> VoteInfo
forall s.
(HasField s "maybe'validator" (Maybe Validator),
HasField s "signedLastBlock" Bool) =>
s -> VoteInfo
f
where
t :: VoteInfo -> b
t VoteInfo{..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe Validator)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'validator" a) =>
LensLike' f s a
PT.maybe'validator LensLike' Identity b (Maybe Validator) -> Maybe Validator -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe Validator
voteInfoValidator Maybe Validator
-> Getting (First Validator) (Maybe Validator) Validator
-> Maybe Validator
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator))
-> ((Validator -> Const (First Validator) Validator)
-> Validator -> Const (First Validator) Validator)
-> Getting (First Validator) (Maybe Validator) Validator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Validator -> Const (First Validator) Validator)
-> Validator -> Const (First Validator) Validator
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Bool
forall (f :: * -> *) s a.
(Functor f, HasField s "signedLastBlock" a) =>
LensLike' f s a
PT.signedLastBlock LensLike' Identity b Bool -> Bool -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
voteInfoSignedLastBlock
f :: s -> VoteInfo
f voteInfo :: s
voteInfo =
VoteInfo :: Maybe Validator -> Bool -> VoteInfo
VoteInfo
{ voteInfoValidator :: Maybe Validator
voteInfoValidator = s
voteInfo s -> Getting (First Validator) s Validator -> Maybe Validator
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First Validator)) s (Maybe Validator)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'validator" a) =>
LensLike' f s a
PT.maybe'validator LensLike' (Const (First Validator)) s (Maybe Validator)
-> ((Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator))
-> Getting (First Validator) s Validator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator))
-> ((Validator -> Const (First Validator) Validator)
-> Validator -> Const (First Validator) Validator)
-> (Validator -> Const (First Validator) Validator)
-> Maybe Validator
-> Const (First Validator) (Maybe Validator)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Validator -> Const (First Validator) Validator)
-> Validator -> Const (First Validator) Validator
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, voteInfoSignedLastBlock :: Bool
voteInfoSignedLastBlock = s
voteInfo 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 "signedLastBlock" a) =>
LensLike' f s a
PT.signedLastBlock
}
data LastCommitInfo = LastCommitInfo
{ LastCommitInfo -> WrappedVal Int32
lastCommitInfoRound :: WrappedVal Int32
, LastCommitInfo -> [VoteInfo]
lastCommitInfoVotes :: [VoteInfo]
} deriving (LastCommitInfo -> LastCommitInfo -> Bool
(LastCommitInfo -> LastCommitInfo -> Bool)
-> (LastCommitInfo -> LastCommitInfo -> Bool) -> Eq LastCommitInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LastCommitInfo -> LastCommitInfo -> Bool
$c/= :: LastCommitInfo -> LastCommitInfo -> Bool
== :: LastCommitInfo -> LastCommitInfo -> Bool
$c== :: LastCommitInfo -> LastCommitInfo -> Bool
Eq, Int -> LastCommitInfo -> ShowS
[LastCommitInfo] -> ShowS
LastCommitInfo -> String
(Int -> LastCommitInfo -> ShowS)
-> (LastCommitInfo -> String)
-> ([LastCommitInfo] -> ShowS)
-> Show LastCommitInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LastCommitInfo] -> ShowS
$cshowList :: [LastCommitInfo] -> ShowS
show :: LastCommitInfo -> String
$cshow :: LastCommitInfo -> String
showsPrec :: Int -> LastCommitInfo -> ShowS
$cshowsPrec :: Int -> LastCommitInfo -> ShowS
Show, (forall x. LastCommitInfo -> Rep LastCommitInfo x)
-> (forall x. Rep LastCommitInfo x -> LastCommitInfo)
-> Generic LastCommitInfo
forall x. Rep LastCommitInfo x -> LastCommitInfo
forall x. LastCommitInfo -> Rep LastCommitInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LastCommitInfo x -> LastCommitInfo
$cfrom :: forall x. LastCommitInfo -> Rep LastCommitInfo x
Generic)
instance ToJSON LastCommitInfo where
toJSON :: LastCommitInfo -> Value
toJSON = Options -> LastCommitInfo -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> LastCommitInfo -> Value)
-> Options -> LastCommitInfo -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "lastCommitInfo"
instance FromJSON LastCommitInfo where
parseJSON :: Value -> Parser LastCommitInfo
parseJSON = String
-> (Object -> Parser LastCommitInfo)
-> Value
-> Parser LastCommitInfo
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject "LastCommitInfo" ((Object -> Parser LastCommitInfo)
-> Value -> Parser LastCommitInfo)
-> (Object -> Parser LastCommitInfo)
-> Value
-> Parser LastCommitInfo
forall a b. (a -> b) -> a -> b
$ \v :: Object
v -> WrappedVal Int32 -> [VoteInfo] -> LastCommitInfo
LastCommitInfo
(WrappedVal Int32 -> [VoteInfo] -> LastCommitInfo)
-> Parser (WrappedVal Int32)
-> Parser ([VoteInfo] -> LastCommitInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (WrappedVal Int32)
forall a. FromJSON a => Object -> Text -> Parser a
.: "infoRound"
Parser ([VoteInfo] -> LastCommitInfo)
-> Parser [VoteInfo] -> Parser LastCommitInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe [VoteInfo])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "infoVotes" Parser (Maybe [VoteInfo]) -> [VoteInfo] -> Parser [VoteInfo]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
instance Wrapped LastCommitInfo where
type Unwrapped LastCommitInfo = PT.LastCommitInfo
_Wrapped' :: p (Unwrapped LastCommitInfo) (f (Unwrapped LastCommitInfo))
-> p LastCommitInfo (f LastCommitInfo)
_Wrapped' = (LastCommitInfo -> LastCommitInfo)
-> (LastCommitInfo -> LastCommitInfo)
-> Iso LastCommitInfo LastCommitInfo LastCommitInfo LastCommitInfo
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso LastCommitInfo -> LastCommitInfo
forall b.
(Message b, HasField b "round" Int32,
HasField b "votes" [VoteInfo]) =>
LastCommitInfo -> b
t LastCommitInfo -> LastCommitInfo
forall s (t :: * -> *).
(HasField s "round" Int32, HasField s "votes" (t VoteInfo),
Traversable t) =>
s -> LastCommitInfo
f
where
t :: LastCommitInfo -> b
t LastCommitInfo{..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Int32
forall (f :: * -> *) s a.
(Functor f, HasField s "round" a) =>
LensLike' f s a
PT.round LensLike' Identity b Int32 -> Int32 -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ WrappedVal Int32 -> Int32
forall a. WrappedVal a -> a
unWrappedVal WrappedVal Int32
lastCommitInfoRound
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b [VoteInfo]
forall (f :: * -> *) s a.
(Functor f, HasField s "votes" a) =>
LensLike' f s a
PT.votes LensLike' Identity b [VoteInfo] -> [VoteInfo] -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [VoteInfo]
lastCommitInfoVotes [VoteInfo]
-> Getting (Endo [VoteInfo]) [VoteInfo] VoteInfo -> [VoteInfo]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> [VoteInfo] -> Const (Endo [VoteInfo]) [VoteInfo]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> [VoteInfo] -> Const (Endo [VoteInfo]) [VoteInfo])
-> ((VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> Getting (Endo [VoteInfo]) [VoteInfo] VoteInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> VoteInfo -> Const (Endo [VoteInfo]) VoteInfo
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
f :: s -> LastCommitInfo
f a :: s
a =
LastCommitInfo :: WrappedVal Int32 -> [VoteInfo] -> LastCommitInfo
LastCommitInfo
{ lastCommitInfoRound :: WrappedVal Int32
lastCommitInfoRound = Int32 -> WrappedVal Int32
forall a. a -> WrappedVal a
WrappedVal (Int32 -> WrappedVal Int32) -> Int32 -> WrappedVal Int32
forall a b. (a -> b) -> a -> b
$ s
a s -> Getting Int32 s Int32 -> Int32
forall s a. s -> Getting a s a -> a
^. Getting Int32 s Int32
forall (f :: * -> *) s a.
(Functor f, HasField s "round" a) =>
LensLike' f s a
PT.round
, lastCommitInfoVotes :: [VoteInfo]
lastCommitInfoVotes = s
a s -> Getting (Endo [VoteInfo]) s VoteInfo -> [VoteInfo]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. LensLike' (Const (Endo [VoteInfo])) s (t VoteInfo)
forall (f :: * -> *) s a.
(Functor f, HasField s "votes" a) =>
LensLike' f s a
PT.votes LensLike' (Const (Endo [VoteInfo])) s (t VoteInfo)
-> ((VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> t VoteInfo -> Const (Endo [VoteInfo]) (t VoteInfo))
-> Getting (Endo [VoteInfo]) s VoteInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> t VoteInfo -> Const (Endo [VoteInfo]) (t VoteInfo)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> t VoteInfo -> Const (Endo [VoteInfo]) (t VoteInfo))
-> ((VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> (VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> t VoteInfo
-> Const (Endo [VoteInfo]) (t VoteInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VoteInfo -> Const (Endo [VoteInfo]) VoteInfo)
-> VoteInfo -> Const (Endo [VoteInfo]) VoteInfo
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
}
data =
{ :: WrappedVal Int32
, :: HexString
} deriving (PartSetHeader -> PartSetHeader -> Bool
(PartSetHeader -> PartSetHeader -> Bool)
-> (PartSetHeader -> PartSetHeader -> Bool) -> Eq PartSetHeader
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PartSetHeader -> PartSetHeader -> Bool
$c/= :: PartSetHeader -> PartSetHeader -> Bool
== :: PartSetHeader -> PartSetHeader -> Bool
$c== :: PartSetHeader -> PartSetHeader -> Bool
Eq, Int -> PartSetHeader -> ShowS
[PartSetHeader] -> ShowS
PartSetHeader -> String
(Int -> PartSetHeader -> ShowS)
-> (PartSetHeader -> String)
-> ([PartSetHeader] -> ShowS)
-> Show PartSetHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PartSetHeader] -> ShowS
$cshowList :: [PartSetHeader] -> ShowS
show :: PartSetHeader -> String
$cshow :: PartSetHeader -> String
showsPrec :: Int -> PartSetHeader -> ShowS
$cshowsPrec :: Int -> PartSetHeader -> ShowS
Show, (forall x. PartSetHeader -> Rep PartSetHeader x)
-> (forall x. Rep PartSetHeader x -> PartSetHeader)
-> Generic PartSetHeader
forall x. Rep PartSetHeader x -> PartSetHeader
forall x. PartSetHeader -> Rep PartSetHeader x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PartSetHeader x -> PartSetHeader
$cfrom :: forall x. PartSetHeader -> Rep PartSetHeader x
Generic)
instance ToJSON PartSetHeader where
toJSON :: PartSetHeader -> Value
toJSON = Options -> PartSetHeader -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> PartSetHeader -> Value)
-> Options -> PartSetHeader -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "partSetHeader"
instance FromJSON PartSetHeader where
parseJSON :: Value -> Parser PartSetHeader
parseJSON = Options -> Value -> Parser PartSetHeader
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser PartSetHeader)
-> Options -> Value -> Parser PartSetHeader
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "partSetHeader"
instance Wrapped PartSetHeader where
type Unwrapped PartSetHeader = PT.PartSetHeader
_Wrapped' :: p (Unwrapped PartSetHeader) (f (Unwrapped PartSetHeader))
-> p PartSetHeader (f PartSetHeader)
_Wrapped' = (PartSetHeader -> PartSetHeader)
-> (PartSetHeader -> PartSetHeader)
-> Iso PartSetHeader PartSetHeader PartSetHeader PartSetHeader
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso PartSetHeader -> PartSetHeader
forall b a.
(Message b, HasField b "hash" a, HasField b "total" Int32,
ByteArray a) =>
PartSetHeader -> b
t PartSetHeader -> PartSetHeader
forall ba s.
(ByteArrayAccess ba, HasField s "hash" ba,
HasField s "total" Int32) =>
s -> PartSetHeader
f
where
t :: PartSetHeader -> b
t PartSetHeader{..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Int32
forall (f :: * -> *) s a.
(Functor f, HasField s "total" a) =>
LensLike' f s a
PT.total LensLike' Identity b Int32 -> Int32 -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ WrappedVal Int32 -> Int32
forall a. WrappedVal a -> a
unWrappedVal WrappedVal Int32
partSetHeaderTotal
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
partSetHeaderHash
f :: s -> PartSetHeader
f a :: s
a =
PartSetHeader :: WrappedVal Int32 -> HexString -> PartSetHeader
PartSetHeader { partSetHeaderTotal :: WrappedVal Int32
partSetHeaderTotal = Int32 -> WrappedVal Int32
forall a. a -> WrappedVal a
WrappedVal (Int32 -> WrappedVal Int32) -> Int32 -> WrappedVal Int32
forall a b. (a -> b) -> a -> b
$ s
a s -> Getting Int32 s Int32 -> Int32
forall s a. s -> Getting a s a -> a
^. Getting Int32 s Int32
forall (f :: * -> *) s a.
(Functor f, HasField s "total" a) =>
LensLike' f s a
PT.total
, partSetHeaderHash :: HexString
partSetHeaderHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (s
a 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)
}
data BlockID = BlockID
{ BlockID -> HexString
blockIDHash :: HexString
, :: Maybe PartSetHeader
} deriving (BlockID -> BlockID -> Bool
(BlockID -> BlockID -> Bool)
-> (BlockID -> BlockID -> Bool) -> Eq BlockID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockID -> BlockID -> Bool
$c/= :: BlockID -> BlockID -> Bool
== :: BlockID -> BlockID -> Bool
$c== :: BlockID -> BlockID -> Bool
Eq, Int -> BlockID -> ShowS
[BlockID] -> ShowS
BlockID -> String
(Int -> BlockID -> ShowS)
-> (BlockID -> String) -> ([BlockID] -> ShowS) -> Show BlockID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockID] -> ShowS
$cshowList :: [BlockID] -> ShowS
show :: BlockID -> String
$cshow :: BlockID -> String
showsPrec :: Int -> BlockID -> ShowS
$cshowsPrec :: Int -> BlockID -> ShowS
Show, (forall x. BlockID -> Rep BlockID x)
-> (forall x. Rep BlockID x -> BlockID) -> Generic BlockID
forall x. Rep BlockID x -> BlockID
forall x. BlockID -> Rep BlockID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlockID x -> BlockID
$cfrom :: forall x. BlockID -> Rep BlockID x
Generic)
instance ToJSON BlockID where
toJSON :: BlockID -> Value
toJSON = Options -> BlockID -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> BlockID -> Value) -> Options -> BlockID -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "blockID"
instance FromJSON BlockID where
parseJSON :: Value -> Parser BlockID
parseJSON = Options -> Value -> Parser BlockID
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser BlockID)
-> Options -> Value -> Parser BlockID
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "blockID"
instance Wrapped BlockID where
type Unwrapped BlockID = PT.BlockID
_Wrapped' :: p (Unwrapped BlockID) (f (Unwrapped BlockID))
-> p BlockID (f BlockID)
_Wrapped' = (BlockID -> BlockID)
-> (BlockID -> BlockID) -> Iso BlockID BlockID BlockID BlockID
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso BlockID -> BlockID
forall b a.
(Message b, ByteArray a, HasField b "hash" a,
HasField b "maybe'partsHeader" (Maybe PartSetHeader)) =>
BlockID -> b
t BlockID -> BlockID
forall ba s.
(ByteArrayAccess ba, HasField s "hash" ba,
HasField s "maybe'partsHeader" (Maybe PartSetHeader)) =>
s -> BlockID
f
where
t :: BlockID -> b
t BlockID{..} =
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
blockIDHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe PartSetHeader)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'partsHeader" a) =>
LensLike' f s a
PT.maybe'partsHeader LensLike' Identity b (Maybe PartSetHeader)
-> Maybe PartSetHeader -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe PartSetHeader
blockIDPartsHeader Maybe PartSetHeader
-> Getting
(First PartSetHeader) (Maybe PartSetHeader) PartSetHeader
-> Maybe PartSetHeader
forall s a. s -> Getting (First a) s a -> Maybe a
^? (PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> Maybe PartSetHeader
-> Const (First PartSetHeader) (Maybe PartSetHeader)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> Maybe PartSetHeader
-> Const (First PartSetHeader) (Maybe PartSetHeader))
-> ((PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> Getting
(First PartSetHeader) (Maybe PartSetHeader) PartSetHeader
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> PartSetHeader -> Const (First PartSetHeader) PartSetHeader
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
f :: s -> BlockID
f a :: s
a =
BlockID :: HexString -> Maybe PartSetHeader -> BlockID
BlockID
{ blockIDHash :: HexString
blockIDHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes(s
a 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)
, blockIDPartsHeader :: Maybe PartSetHeader
blockIDPartsHeader = s
a s
-> Getting (First PartSetHeader) s PartSetHeader
-> Maybe PartSetHeader
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First PartSetHeader)) s (Maybe PartSetHeader)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'partsHeader" a) =>
LensLike' f s a
PT.maybe'partsHeader LensLike' (Const (First PartSetHeader)) s (Maybe PartSetHeader)
-> ((PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> Maybe PartSetHeader
-> Const (First PartSetHeader) (Maybe PartSetHeader))
-> Getting (First PartSetHeader) s PartSetHeader
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> Maybe PartSetHeader
-> Const (First PartSetHeader) (Maybe PartSetHeader)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> Maybe PartSetHeader
-> Const (First PartSetHeader) (Maybe PartSetHeader))
-> ((PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> (PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> Maybe PartSetHeader
-> Const (First PartSetHeader) (Maybe PartSetHeader)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PartSetHeader -> Const (First PartSetHeader) PartSetHeader)
-> PartSetHeader -> Const (First PartSetHeader) PartSetHeader
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
}
data Version = Version
{ Version -> WrappedVal Word64
versionBlock :: WrappedVal Word64
, Version -> WrappedVal Word64
versionApp :: WrappedVal Word64
} deriving (Version -> Version -> Bool
(Version -> Version -> Bool)
-> (Version -> Version -> Bool) -> Eq Version
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Version -> Version -> Bool
$c/= :: Version -> Version -> Bool
== :: Version -> Version -> Bool
$c== :: Version -> Version -> Bool
Eq, Int -> Version -> ShowS
[Version] -> ShowS
Version -> String
(Int -> Version -> ShowS)
-> (Version -> String) -> ([Version] -> ShowS) -> Show Version
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Version] -> ShowS
$cshowList :: [Version] -> ShowS
show :: Version -> String
$cshow :: Version -> String
showsPrec :: Int -> Version -> ShowS
$cshowsPrec :: Int -> Version -> ShowS
Show, (forall x. Version -> Rep Version x)
-> (forall x. Rep Version x -> Version) -> Generic Version
forall x. Rep Version x -> Version
forall x. Version -> Rep Version x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Version x -> Version
$cfrom :: forall x. Version -> Rep Version x
Generic)
instance ToJSON Version where
toJSON :: Version -> Value
toJSON = Options -> Version -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Version -> Value) -> Options -> Version -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "version"
instance FromJSON Version where
parseJSON :: Value -> Parser Version
parseJSON = Options -> Value -> Parser Version
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Version)
-> Options -> Value -> Parser Version
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "version"
instance Wrapped Version where
type Unwrapped Version = PT.Version
_Wrapped' :: p (Unwrapped Version) (f (Unwrapped Version))
-> p Version (f Version)
_Wrapped' = (Version -> Version)
-> (Version -> Version) -> Iso Version Version Version Version
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Version -> Version
forall b.
(Message b, HasField b "app" Word64, HasField b "block" Word64) =>
Version -> b
t Version -> Version
forall s.
(HasField s "app" Word64, HasField s "block" Word64) =>
s -> Version
f
where
t :: Version -> b
t Version{..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "block" a) =>
LensLike' f s a
PT.block LensLike' Identity b Word64 -> Word64 -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ WrappedVal Word64 -> Word64
forall a. WrappedVal a -> a
unWrappedVal WrappedVal Word64
versionBlock
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Word64
forall (f :: * -> *) s a.
(Functor f, HasField s "app" a) =>
LensLike' f s a
PT.app LensLike' Identity b Word64 -> Word64 -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ WrappedVal Word64 -> Word64
forall a. WrappedVal a -> a
unWrappedVal WrappedVal Word64
versionApp
f :: s -> Version
f a :: s
a =
Version :: WrappedVal Word64 -> WrappedVal Word64 -> Version
Version
{ versionBlock :: WrappedVal Word64
versionBlock = Word64 -> WrappedVal Word64
forall a. a -> WrappedVal a
WrappedVal (Word64 -> WrappedVal Word64) -> Word64 -> WrappedVal Word64
forall a b. (a -> b) -> a -> b
$ s
a 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 "block" a) =>
LensLike' f s a
PT.block
, versionApp :: WrappedVal Word64
versionApp = Word64 -> WrappedVal Word64
forall a. a -> WrappedVal a
WrappedVal (Word64 -> WrappedVal Word64) -> Word64 -> WrappedVal Word64
forall a b. (a -> b) -> a -> b
$ s
a 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 "app" a) =>
LensLike' f s a
PT.app
}
data =
{ :: Maybe Version
, :: Text
, :: WrappedVal Int64
, :: Maybe Timestamp
, :: WrappedVal Int64
, :: WrappedVal Int64
, :: Maybe BlockID
, :: HexString
, :: HexString
, :: HexString
, :: HexString
, :: HexString
, :: HexString
, :: HexString
, :: HexString
, :: HexString
} deriving (Header -> Header -> Bool
(Header -> Header -> Bool)
-> (Header -> Header -> Bool) -> Eq Header
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Header -> Header -> Bool
$c/= :: Header -> Header -> Bool
== :: Header -> Header -> Bool
$c== :: Header -> Header -> Bool
Eq, Int -> Header -> ShowS
[Header] -> ShowS
Header -> String
(Int -> Header -> ShowS)
-> (Header -> String) -> ([Header] -> ShowS) -> Show Header
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Header] -> ShowS
$cshowList :: [Header] -> ShowS
show :: Header -> String
$cshow :: Header -> String
showsPrec :: Int -> Header -> ShowS
$cshowsPrec :: Int -> Header -> ShowS
Show, (forall x. Header -> Rep Header x)
-> (forall x. Rep Header x -> Header) -> Generic Header
forall x. Rep Header x -> Header
forall x. Header -> Rep Header x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Header x -> Header
$cfrom :: forall x. Header -> Rep Header x
Generic)
instance ToJSON Header where
toJSON :: Header -> Value
toJSON = Options -> Header -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Header -> Value) -> Options -> Header -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "header"
instance FromJSON Header where
parseJSON :: Value -> Parser Header
parseJSON = Options -> Value -> Parser Header
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Header)
-> Options -> Value -> Parser Header
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "header"
instance Wrapped Header where
type Unwrapped Header = PT.Header
_Wrapped' :: p (Unwrapped Header) (f (Unwrapped Header)) -> p Header (f Header)
_Wrapped' = (Header -> Header)
-> (Header -> Header) -> Iso Header Header Header Header
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Header -> Header
forall b a a a a a a a a a.
(Message b, HasField b "appHash" a, HasField b "chainId" Text,
HasField b "consensusHash" a, HasField b "dataHash" a,
HasField b "evidenceHash" a, HasField b "height" Int64,
HasField b "lastCommitHash" a, HasField b "lastResultsHash" a,
HasField b "maybe'lastBlockId" (Maybe BlockID),
HasField b "maybe'time" (Maybe Timestamp),
HasField b "maybe'version" (Maybe Version),
HasField b "nextValidatorsHash" a, HasField b "numTxs" Int64,
HasField b "proposerAddress" a, HasField b "totalTxs" Int64,
HasField b "validatorsHash" a, ByteArray a, ByteArray a,
ByteArray a, ByteArray a, ByteArray a, ByteArray a, ByteArray a,
ByteArray a, ByteArray a) =>
Header -> b
t Header -> Header
forall ba ba ba ba ba ba ba ba ba s.
(ByteArrayAccess ba, ByteArrayAccess ba, ByteArrayAccess ba,
ByteArrayAccess ba, ByteArrayAccess ba, ByteArrayAccess ba,
ByteArrayAccess ba, ByteArrayAccess ba, ByteArrayAccess ba,
HasField s "appHash" ba, HasField s "chainId" Text,
HasField s "consensusHash" ba, HasField s "dataHash" ba,
HasField s "evidenceHash" ba, HasField s "height" Int64,
HasField s "lastCommitHash" ba, HasField s "lastResultsHash" ba,
HasField s "maybe'lastBlockId" (Maybe BlockID),
HasField s "maybe'time" (Maybe Timestamp),
HasField s "maybe'version" (Maybe Version),
HasField s "nextValidatorsHash" ba, HasField s "numTxs" Int64,
HasField s "proposerAddress" ba, HasField s "totalTxs" Int64,
HasField s "validatorsHash" ba) =>
s -> Header
f
where
t :: Header -> b
t Header{..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe Version)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'version" a) =>
LensLike' f s a
PT.maybe'version LensLike' Identity b (Maybe Version) -> Maybe Version -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe Version
headerVersion Maybe Version
-> Getting (First Version) (Maybe Version) Version -> Maybe Version
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Version -> Const (First Version) Version)
-> Maybe Version -> Const (First Version) (Maybe Version)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Version -> Const (First Version) Version)
-> Maybe Version -> Const (First Version) (Maybe Version))
-> ((Version -> Const (First Version) Version)
-> Version -> Const (First Version) Version)
-> Getting (First Version) (Maybe Version) Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Version -> Const (First Version) Version)
-> Version -> Const (First Version) Version
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
headerChainId
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
headerHeight
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
headerTime 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 Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "numTxs" a) =>
LensLike' f s a
PT.numTxs 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
headerNumTxs
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "totalTxs" a) =>
LensLike' f s a
PT.totalTxs 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
headerTotalTxs
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe BlockID)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'lastBlockId" a) =>
LensLike' f s a
PT.maybe'lastBlockId LensLike' Identity b (Maybe BlockID) -> Maybe BlockID -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe BlockID
headerLastBlockId Maybe BlockID
-> Getting (First BlockID) (Maybe BlockID) BlockID -> Maybe BlockID
forall s a. s -> Getting (First a) s a -> Maybe a
^? (BlockID -> Const (First BlockID) BlockID)
-> Maybe BlockID -> Const (First BlockID) (Maybe BlockID)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((BlockID -> Const (First BlockID) BlockID)
-> Maybe BlockID -> Const (First BlockID) (Maybe BlockID))
-> ((BlockID -> Const (First BlockID) BlockID)
-> BlockID -> Const (First BlockID) BlockID)
-> Getting (First BlockID) (Maybe BlockID) BlockID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BlockID -> Const (First BlockID) BlockID)
-> BlockID -> Const (First BlockID) BlockID
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 "lastCommitHash" a) =>
LensLike' f s a
PT.lastCommitHash 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
headerLastCommitHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "dataHash" a) =>
LensLike' f s a
PT.dataHash 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
headerDataHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "validatorsHash" a) =>
LensLike' f s a
PT.validatorsHash 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
headerValidatorsHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "nextValidatorsHash" a) =>
LensLike' f s a
PT.nextValidatorsHash 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
headerNextValidatorsHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "consensusHash" a) =>
LensLike' f s a
PT.consensusHash 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
headerConsensusHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "appHash" a) =>
LensLike' f s a
PT.appHash 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
headerAppHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "lastResultsHash" a) =>
LensLike' f s a
PT.lastResultsHash 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
headerLastResultsHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "evidenceHash" a) =>
LensLike' f s a
PT.evidenceHash 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
headerEvidenceHash
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "proposerAddress" a) =>
LensLike' f s a
PT.proposerAddress 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
headerProposerAddress
f :: s -> Header
f a :: s
a =
Header :: Maybe Version
-> Text
-> WrappedVal Int64
-> Maybe Timestamp
-> WrappedVal Int64
-> WrappedVal Int64
-> Maybe BlockID
-> HexString
-> HexString
-> HexString
-> HexString
-> HexString
-> HexString
-> HexString
-> HexString
-> HexString
-> Header
Header
{ headerVersion :: Maybe Version
headerVersion = s
a s -> Getting (First Version) s Version -> Maybe Version
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First Version)) s (Maybe Version)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'version" a) =>
LensLike' f s a
PT.maybe'version LensLike' (Const (First Version)) s (Maybe Version)
-> ((Version -> Const (First Version) Version)
-> Maybe Version -> Const (First Version) (Maybe Version))
-> Getting (First Version) s Version
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Version -> Const (First Version) Version)
-> Maybe Version -> Const (First Version) (Maybe Version)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Version -> Const (First Version) Version)
-> Maybe Version -> Const (First Version) (Maybe Version))
-> ((Version -> Const (First Version) Version)
-> Version -> Const (First Version) Version)
-> (Version -> Const (First Version) Version)
-> Maybe Version
-> Const (First Version) (Maybe Version)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Version -> Const (First Version) Version)
-> Version -> Const (First Version) Version
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, headerChainId :: Text
headerChainId = s
a 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
, headerHeight :: WrappedVal Int64
headerHeight = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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
, headerTime :: Maybe Timestamp
headerTime = s
a 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'
, headerNumTxs :: WrappedVal Int64
headerNumTxs = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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 "numTxs" a) =>
LensLike' f s a
PT.numTxs
, headerTotalTxs :: WrappedVal Int64
headerTotalTxs = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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 "totalTxs" a) =>
LensLike' f s a
PT.totalTxs
, headerLastBlockId :: Maybe BlockID
headerLastBlockId = s
a s -> Getting (First BlockID) s BlockID -> Maybe BlockID
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First BlockID)) s (Maybe BlockID)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'lastBlockId" a) =>
LensLike' f s a
PT.maybe'lastBlockId LensLike' (Const (First BlockID)) s (Maybe BlockID)
-> ((BlockID -> Const (First BlockID) BlockID)
-> Maybe BlockID -> Const (First BlockID) (Maybe BlockID))
-> Getting (First BlockID) s BlockID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BlockID -> Const (First BlockID) BlockID)
-> Maybe BlockID -> Const (First BlockID) (Maybe BlockID)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((BlockID -> Const (First BlockID) BlockID)
-> Maybe BlockID -> Const (First BlockID) (Maybe BlockID))
-> ((BlockID -> Const (First BlockID) BlockID)
-> BlockID -> Const (First BlockID) BlockID)
-> (BlockID -> Const (First BlockID) BlockID)
-> Maybe BlockID
-> Const (First BlockID) (Maybe BlockID)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BlockID -> Const (First BlockID) BlockID)
-> BlockID -> Const (First BlockID) BlockID
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, headerLastCommitHash :: HexString
headerLastCommitHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
a 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 "lastCommitHash" a) =>
LensLike' f s a
PT.lastCommitHash
, headerDataHash :: HexString
headerDataHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
a 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 "dataHash" a) =>
LensLike' f s a
PT.dataHash
, headerValidatorsHash :: HexString
headerValidatorsHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
a 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 "validatorsHash" a) =>
LensLike' f s a
PT.validatorsHash
, headerNextValidatorsHash :: HexString
headerNextValidatorsHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
a 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 "nextValidatorsHash" a) =>
LensLike' f s a
PT.nextValidatorsHash
, headerConsensusHash :: HexString
headerConsensusHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
a 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 "consensusHash" a) =>
LensLike' f s a
PT.consensusHash
, headerAppHash :: HexString
headerAppHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
a 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 "appHash" a) =>
LensLike' f s a
PT.appHash
, headerLastResultsHash :: HexString
headerLastResultsHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
a 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 "lastResultsHash" a) =>
LensLike' f s a
PT.lastResultsHash
, headerEvidenceHash :: HexString
headerEvidenceHash = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
a 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 "evidenceHash" a) =>
LensLike' f s a
PT.evidenceHash
, headerProposerAddress :: HexString
headerProposerAddress = ba -> HexString
forall ba. ByteArrayAccess ba => ba -> HexString
Hex.fromBytes (ba -> HexString) -> ba -> HexString
forall a b. (a -> b) -> a -> b
$ s
a 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 "proposerAddress" a) =>
LensLike' f s a
PT.proposerAddress
}
data Evidence = Evidence
{ Evidence -> Text
evidenceType :: Text
, Evidence -> Maybe Validator
evidenceValidator :: Maybe Validator
, Evidence -> WrappedVal Int64
evidenceHeight :: WrappedVal Int64
, Evidence -> Maybe Timestamp
evidenceTime :: Maybe Timestamp
, Evidence -> WrappedVal Int64
evidenceTotalVotingPower :: WrappedVal Int64
} deriving (Evidence -> Evidence -> Bool
(Evidence -> Evidence -> Bool)
-> (Evidence -> Evidence -> Bool) -> Eq Evidence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Evidence -> Evidence -> Bool
$c/= :: Evidence -> Evidence -> Bool
== :: Evidence -> Evidence -> Bool
$c== :: Evidence -> Evidence -> Bool
Eq, Int -> Evidence -> ShowS
[Evidence] -> ShowS
Evidence -> String
(Int -> Evidence -> ShowS)
-> (Evidence -> String) -> ([Evidence] -> ShowS) -> Show Evidence
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Evidence] -> ShowS
$cshowList :: [Evidence] -> ShowS
show :: Evidence -> String
$cshow :: Evidence -> String
showsPrec :: Int -> Evidence -> ShowS
$cshowsPrec :: Int -> Evidence -> ShowS
Show, (forall x. Evidence -> Rep Evidence x)
-> (forall x. Rep Evidence x -> Evidence) -> Generic Evidence
forall x. Rep Evidence x -> Evidence
forall x. Evidence -> Rep Evidence x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Evidence x -> Evidence
$cfrom :: forall x. Evidence -> Rep Evidence x
Generic)
instance ToJSON Evidence where
toJSON :: Evidence -> Value
toJSON = Options -> Evidence -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Evidence -> Value) -> Options -> Evidence -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "evidence"
instance FromJSON Evidence where
parseJSON :: Value -> Parser Evidence
parseJSON = Options -> Value -> Parser Evidence
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser Evidence)
-> Options -> Value -> Parser Evidence
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "evidence"
instance Wrapped Evidence where
type Unwrapped Evidence = PT.Evidence
_Wrapped' :: p (Unwrapped Evidence) (f (Unwrapped Evidence))
-> p Evidence (f Evidence)
_Wrapped' = (Evidence -> Evidence)
-> (Evidence -> Evidence)
-> Iso Evidence Evidence Evidence Evidence
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Evidence -> Evidence
forall b.
(Message b, HasField b "height" Int64,
HasField b "maybe'time" (Maybe Timestamp),
HasField b "maybe'validator" (Maybe Validator),
HasField b "totalVotingPower" Int64, HasField b "type'" Text) =>
Evidence -> b
t Evidence -> Evidence
forall s.
(HasField s "height" Int64,
HasField s "maybe'time" (Maybe Timestamp),
HasField s "maybe'validator" (Maybe Validator),
HasField s "totalVotingPower" Int64, HasField s "type'" Text) =>
s -> Evidence
f
where
t :: Evidence -> b
t Evidence{..} =
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 "type'" a) =>
LensLike' f s a
PT.type' LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
evidenceType
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b (Maybe Validator)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'validator" a) =>
LensLike' f s a
PT.maybe'validator LensLike' Identity b (Maybe Validator) -> Maybe Validator -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Maybe Validator
evidenceValidator Maybe Validator
-> Getting (First Validator) (Maybe Validator) Validator
-> Maybe Validator
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator))
-> ((Validator -> Const (First Validator) Validator)
-> Validator -> Const (First Validator) Validator)
-> Getting (First Validator) (Maybe Validator) Validator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Validator -> Const (First Validator) Validator)
-> Validator -> Const (First Validator) Validator
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
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
evidenceHeight
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
evidenceTime 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 Int64
forall (f :: * -> *) s a.
(Functor f, HasField s "totalVotingPower" a) =>
LensLike' f s a
PT.totalVotingPower 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
evidenceTotalVotingPower
f :: s -> Evidence
f a :: s
a =
Evidence :: Text
-> Maybe Validator
-> WrappedVal Int64
-> Maybe Timestamp
-> WrappedVal Int64
-> Evidence
Evidence
{ evidenceType :: Text
evidenceType = s
a 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 "type'" a) =>
LensLike' f s a
PT.type'
, evidenceValidator :: Maybe Validator
evidenceValidator = s
a s -> Getting (First Validator) s Validator -> Maybe Validator
forall s a. s -> Getting (First a) s a -> Maybe a
^? LensLike' (Const (First Validator)) s (Maybe Validator)
forall (f :: * -> *) s a.
(Functor f, HasField s "maybe'validator" a) =>
LensLike' f s a
PT.maybe'validator LensLike' (Const (First Validator)) s (Maybe Validator)
-> ((Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator))
-> Getting (First Validator) s Validator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just ((Validator -> Const (First Validator) Validator)
-> Maybe Validator -> Const (First Validator) (Maybe Validator))
-> ((Validator -> Const (First Validator) Validator)
-> Validator -> Const (First Validator) Validator)
-> (Validator -> Const (First Validator) Validator)
-> Maybe Validator
-> Const (First Validator) (Maybe Validator)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Validator -> Const (First Validator) Validator)
-> Validator -> Const (First Validator) Validator
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
, evidenceHeight :: WrappedVal Int64
evidenceHeight = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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
, evidenceTime :: Maybe Timestamp
evidenceTime = s
a 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'
, evidenceTotalVotingPower :: WrappedVal Int64
evidenceTotalVotingPower = Int64 -> WrappedVal Int64
forall a. a -> WrappedVal a
WrappedVal (Int64 -> WrappedVal Int64) -> Int64 -> WrappedVal Int64
forall a b. (a -> b) -> a -> b
$ s
a 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 "totalVotingPower" a) =>
LensLike' f s a
PT.totalVotingPower
}
data KVPair = KVPair
{ KVPair -> Base64String
kVPairKey :: Base64String
, KVPair -> Base64String
kVPairValue :: Base64String
} deriving (KVPair -> KVPair -> Bool
(KVPair -> KVPair -> Bool)
-> (KVPair -> KVPair -> Bool) -> Eq KVPair
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KVPair -> KVPair -> Bool
$c/= :: KVPair -> KVPair -> Bool
== :: KVPair -> KVPair -> Bool
$c== :: KVPair -> KVPair -> Bool
Eq, Int -> KVPair -> ShowS
[KVPair] -> ShowS
KVPair -> String
(Int -> KVPair -> ShowS)
-> (KVPair -> String) -> ([KVPair] -> ShowS) -> Show KVPair
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KVPair] -> ShowS
$cshowList :: [KVPair] -> ShowS
show :: KVPair -> String
$cshow :: KVPair -> String
showsPrec :: Int -> KVPair -> ShowS
$cshowsPrec :: Int -> KVPair -> ShowS
Show, (forall x. KVPair -> Rep KVPair x)
-> (forall x. Rep KVPair x -> KVPair) -> Generic KVPair
forall x. Rep KVPair x -> KVPair
forall x. KVPair -> Rep KVPair x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KVPair x -> KVPair
$cfrom :: forall x. KVPair -> Rep KVPair x
Generic)
instance ToJSON KVPair where
toJSON :: KVPair -> Value
toJSON = Options -> KVPair -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> KVPair -> Value) -> Options -> KVPair -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "kVPair"
instance FromJSON KVPair where
parseJSON :: Value -> Parser KVPair
parseJSON = Options -> Value -> Parser KVPair
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser KVPair)
-> Options -> Value -> Parser KVPair
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "kVPair"
instance Wrapped KVPair where
type Unwrapped KVPair = CT.KVPair
_Wrapped' :: p (Unwrapped KVPair) (f (Unwrapped KVPair)) -> p KVPair (f KVPair)
_Wrapped' = (KVPair -> KVPair)
-> (KVPair -> KVPair) -> Iso KVPair KVPair KVPair KVPair
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso KVPair -> KVPair
forall b a a.
(Message b, HasField b "key" a, HasField b "value" a, ByteArray a,
ByteArray a) =>
KVPair -> b
t KVPair -> KVPair
forall ba ba s.
(ByteArrayAccess ba, ByteArrayAccess ba, HasField s "key" ba,
HasField s "value" ba) =>
s -> KVPair
f
where
t :: KVPair -> b
t KVPair{..} =
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 "key" a) =>
LensLike' f s a
CT.key 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
kVPairKey
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "value" a) =>
LensLike' f s a
CT.value 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
kVPairValue
f :: s -> KVPair
f a :: s
a =
KVPair :: Base64String -> Base64String -> KVPair
KVPair
{ kVPairKey :: Base64String
kVPairKey = ba -> Base64String
forall ba. ByteArrayAccess ba => ba -> Base64String
Base64.fromBytes (ba -> Base64String) -> ba -> Base64String
forall a b. (a -> b) -> a -> b
$ s
a 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 "key" a) =>
LensLike' f s a
CT.key
, kVPairValue :: Base64String
kVPairValue = ba -> Base64String
forall ba. ByteArrayAccess ba => ba -> Base64String
Base64.fromBytes (ba -> Base64String) -> ba -> Base64String
forall a b. (a -> b) -> a -> b
$ s
a 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 "value" a) =>
LensLike' f s a
CT.value
}
data Proof = Proof
{ Proof -> [ProofOp]
proofOps :: [ProofOp]
} deriving (Proof -> Proof -> Bool
(Proof -> Proof -> Bool) -> (Proof -> Proof -> Bool) -> Eq Proof
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Proof -> Proof -> Bool
$c/= :: Proof -> Proof -> Bool
== :: Proof -> Proof -> Bool
$c== :: Proof -> Proof -> Bool
Eq, Int -> Proof -> ShowS
[Proof] -> ShowS
Proof -> String
(Int -> Proof -> ShowS)
-> (Proof -> String) -> ([Proof] -> ShowS) -> Show Proof
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Proof] -> ShowS
$cshowList :: [Proof] -> ShowS
show :: Proof -> String
$cshow :: Proof -> String
showsPrec :: Int -> Proof -> ShowS
$cshowsPrec :: Int -> Proof -> ShowS
Show, (forall x. Proof -> Rep Proof x)
-> (forall x. Rep Proof x -> Proof) -> Generic Proof
forall x. Rep Proof x -> Proof
forall x. Proof -> Rep Proof x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Proof x -> Proof
$cfrom :: forall x. Proof -> Rep Proof x
Generic)
instance ToJSON Proof where
toJSON :: Proof -> Value
toJSON = Options -> Proof -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Proof -> Value) -> Options -> Proof -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "proof"
instance FromJSON Proof where
parseJSON :: Value -> Parser Proof
parseJSON = String -> (Object -> Parser Proof) -> Value -> Parser Proof
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject "Proof" ((Object -> Parser Proof) -> Value -> Parser Proof)
-> (Object -> Parser Proof) -> Value -> Parser Proof
forall a b. (a -> b) -> a -> b
$ \v :: Object
v -> [ProofOp] -> Proof
Proof
([ProofOp] -> Proof) -> Parser [ProofOp] -> Parser Proof
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe [ProofOp])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "ops" Parser (Maybe [ProofOp]) -> [ProofOp] -> Parser [ProofOp]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
instance Wrapped Proof where
type Unwrapped Proof = MT.Proof
_Wrapped' :: p (Unwrapped Proof) (f (Unwrapped Proof)) -> p Proof (f Proof)
_Wrapped' = (Proof -> Proof) -> (Proof -> Proof) -> Iso Proof Proof Proof Proof
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Proof -> Proof
forall b. (Message b, HasField b "ops" [ProofOp]) => Proof -> b
t Proof -> Proof
forall s (t :: * -> *).
(HasField s "ops" (t ProofOp), Traversable t) =>
s -> Proof
f
where
t :: Proof -> b
t Proof{..} =
b
forall msg. Message msg => msg
defMessage
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b [ProofOp]
forall (f :: * -> *) s a.
(Functor f, HasField s "ops" a) =>
LensLike' f s a
MT.ops LensLike' Identity b [ProofOp] -> [ProofOp] -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [ProofOp]
proofOps [ProofOp]
-> Getting (Endo [ProofOp]) [ProofOp] ProofOp -> [ProofOp]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> [ProofOp] -> Const (Endo [ProofOp]) [ProofOp]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> [ProofOp] -> Const (Endo [ProofOp]) [ProofOp])
-> ((ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> Getting (Endo [ProofOp]) [ProofOp] ProofOp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> ProofOp -> Const (Endo [ProofOp]) ProofOp
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
f :: s -> Proof
f a :: s
a =
Proof :: [ProofOp] -> Proof
Proof
{ proofOps :: [ProofOp]
proofOps = s
a s -> Getting (Endo [ProofOp]) s ProofOp -> [ProofOp]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. LensLike' (Const (Endo [ProofOp])) s (t ProofOp)
forall (f :: * -> *) s a.
(Functor f, HasField s "ops" a) =>
LensLike' f s a
MT.ops LensLike' (Const (Endo [ProofOp])) s (t ProofOp)
-> ((ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> t ProofOp -> Const (Endo [ProofOp]) (t ProofOp))
-> Getting (Endo [ProofOp]) s ProofOp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> t ProofOp -> Const (Endo [ProofOp]) (t ProofOp)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> t ProofOp -> Const (Endo [ProofOp]) (t ProofOp))
-> ((ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> (ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> t ProofOp
-> Const (Endo [ProofOp]) (t ProofOp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProofOp -> Const (Endo [ProofOp]) ProofOp)
-> ProofOp -> Const (Endo [ProofOp]) ProofOp
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
}
data ProofOp = ProofOp
{ ProofOp -> Text
proofOpType :: Text
, ProofOp -> Base64String
proofOpKey :: Base64String
, ProofOp -> Base64String
proofOpData :: Base64String
} deriving (ProofOp -> ProofOp -> Bool
(ProofOp -> ProofOp -> Bool)
-> (ProofOp -> ProofOp -> Bool) -> Eq ProofOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProofOp -> ProofOp -> Bool
$c/= :: ProofOp -> ProofOp -> Bool
== :: ProofOp -> ProofOp -> Bool
$c== :: ProofOp -> ProofOp -> Bool
Eq, Int -> ProofOp -> ShowS
[ProofOp] -> ShowS
ProofOp -> String
(Int -> ProofOp -> ShowS)
-> (ProofOp -> String) -> ([ProofOp] -> ShowS) -> Show ProofOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProofOp] -> ShowS
$cshowList :: [ProofOp] -> ShowS
show :: ProofOp -> String
$cshow :: ProofOp -> String
showsPrec :: Int -> ProofOp -> ShowS
$cshowsPrec :: Int -> ProofOp -> ShowS
Show, (forall x. ProofOp -> Rep ProofOp x)
-> (forall x. Rep ProofOp x -> ProofOp) -> Generic ProofOp
forall x. Rep ProofOp x -> ProofOp
forall x. ProofOp -> Rep ProofOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProofOp x -> ProofOp
$cfrom :: forall x. ProofOp -> Rep ProofOp x
Generic)
instance ToJSON ProofOp where
toJSON :: ProofOp -> Value
toJSON = Options -> ProofOp -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> ProofOp -> Value) -> Options -> ProofOp -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "proofOp"
instance FromJSON ProofOp where
parseJSON :: Value -> Parser ProofOp
parseJSON = Options -> Value -> Parser ProofOp
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser ProofOp)
-> Options -> Value -> Parser ProofOp
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "proofOp"
instance Wrapped ProofOp where
type Unwrapped ProofOp = MT.ProofOp
_Wrapped' :: p (Unwrapped ProofOp) (f (Unwrapped ProofOp))
-> p ProofOp (f ProofOp)
_Wrapped' = (ProofOp -> ProofOp)
-> (ProofOp -> ProofOp) -> Iso ProofOp ProofOp ProofOp ProofOp
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ProofOp -> ProofOp
forall b a a.
(Message b, HasField b "data'" a, HasField b "key" a,
HasField b "type'" Text, ByteArray a, ByteArray a) =>
ProofOp -> b
t ProofOp -> ProofOp
forall ba ba s.
(ByteArrayAccess ba, ByteArrayAccess ba, HasField s "data'" ba,
HasField s "key" ba, HasField s "type'" Text) =>
s -> ProofOp
f
where
t :: ProofOp -> b
t ProofOp{..} =
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 "type'" a) =>
LensLike' f s a
MT.type' LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
proofOpType
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b a
forall (f :: * -> *) s a.
(Functor f, HasField s "key" a) =>
LensLike' f s a
MT.key 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
proofOpKey
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
MT.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
proofOpData
f :: s -> ProofOp
f a :: s
a =
ProofOp :: Text -> Base64String -> Base64String -> ProofOp
ProofOp
{ proofOpType :: Text
proofOpType = s
a 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 "type'" a) =>
LensLike' f s a
MT.type'
, proofOpKey :: Base64String
proofOpKey = ba -> Base64String
forall ba. ByteArrayAccess ba => ba -> Base64String
Base64.fromBytes (ba -> Base64String) -> ba -> Base64String
forall a b. (a -> b) -> a -> b
$ s
a 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 "key" a) =>
LensLike' f s a
MT.key
, proofOpData :: Base64String
proofOpData = ba -> Base64String
forall ba. ByteArrayAccess ba => ba -> Base64String
Base64.fromBytes (ba -> Base64String) -> ba -> Base64String
forall a b. (a -> b) -> a -> b
$ s
a 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
MT.data'
}
data Event = Event
{ Event -> Text
eventType :: Text
, Event -> [KVPair]
eventAttributes :: [KVPair]
} deriving (Event -> Event -> Bool
(Event -> Event -> Bool) -> (Event -> Event -> Bool) -> Eq Event
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c== :: Event -> Event -> Bool
Eq, Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
(Int -> Event -> ShowS)
-> (Event -> String) -> ([Event] -> ShowS) -> Show Event
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show, (forall x. Event -> Rep Event x)
-> (forall x. Rep Event x -> Event) -> Generic Event
forall x. Rep Event x -> Event
forall x. Event -> Rep Event x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Event x -> Event
$cfrom :: forall x. Event -> Rep Event x
Generic)
instance ToJSON Event where
toJSON :: Event -> Value
toJSON = Options -> Event -> Value
forall a.
(Generic a, GToJSON Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON (Options -> Event -> Value) -> Options -> Event -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
defaultABCIOptions "event"
instance FromJSON Event where
parseJSON :: Value -> Parser Event
parseJSON = String -> (Object -> Parser Event) -> Value -> Parser Event
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject "Event" ((Object -> Parser Event) -> Value -> Parser Event)
-> (Object -> Parser Event) -> Value -> Parser Event
forall a b. (a -> b) -> a -> b
$ \v :: Object
v -> Text -> [KVPair] -> Event
Event
(Text -> [KVPair] -> Event)
-> Parser Text -> Parser ([KVPair] -> Event)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: "type"
Parser ([KVPair] -> Event) -> Parser [KVPair] -> Parser Event
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe [KVPair])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "attributes" Parser (Maybe [KVPair]) -> [KVPair] -> Parser [KVPair]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
instance Wrapped Event where
type Unwrapped Event = PT.Event
_Wrapped' :: p (Unwrapped Event) (f (Unwrapped Event)) -> p Event (f Event)
_Wrapped' = (Event -> Event) -> (Event -> Event) -> Iso Event Event Event Event
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Event -> Event
forall b.
(Message b, HasField b "attributes" [KVPair],
HasField b "type'" Text) =>
Event -> b
t Event -> Event
forall s (t :: * -> *).
(HasField s "attributes" (t KVPair), HasField s "type'" Text,
Traversable t) =>
s -> Event
f
where
t :: Event -> b
t Event{..} =
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 "type'" a) =>
LensLike' f s a
PT.type' LensLike' Identity b Text -> Text -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
eventType
b -> (b -> b) -> b
forall a b. a -> (a -> b) -> b
& LensLike' Identity b [KVPair]
forall (f :: * -> *) s a.
(Functor f, HasField s "attributes" a) =>
LensLike' f s a
PT.attributes LensLike' Identity b [KVPair] -> [KVPair] -> b -> b
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [KVPair]
eventAttributes [KVPair] -> Getting (Endo [KVPair]) [KVPair] KVPair -> [KVPair]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (KVPair -> Const (Endo [KVPair]) KVPair)
-> [KVPair] -> Const (Endo [KVPair]) [KVPair]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((KVPair -> Const (Endo [KVPair]) KVPair)
-> [KVPair] -> Const (Endo [KVPair]) [KVPair])
-> ((KVPair -> Const (Endo [KVPair]) KVPair)
-> KVPair -> Const (Endo [KVPair]) KVPair)
-> Getting (Endo [KVPair]) [KVPair] KVPair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (KVPair -> Const (Endo [KVPair]) KVPair)
-> KVPair -> Const (Endo [KVPair]) KVPair
forall s. Wrapped s => Iso' s (Unwrapped s)
_Wrapped'
f :: s -> Event
f a :: s
a =
Event :: Text -> [KVPair] -> Event
Event
{ eventType :: Text
eventType = s
a 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 "type'" a) =>
LensLike' f s a
PT.type'
, eventAttributes :: [KVPair]
eventAttributes = s
a s -> Getting (Endo [KVPair]) s KVPair -> [KVPair]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. LensLike' (Const (Endo [KVPair])) s (t KVPair)
forall (f :: * -> *) s a.
(Functor f, HasField s "attributes" a) =>
LensLike' f s a
PT.attributes LensLike' (Const (Endo [KVPair])) s (t KVPair)
-> ((KVPair -> Const (Endo [KVPair]) KVPair)
-> t KVPair -> Const (Endo [KVPair]) (t KVPair))
-> Getting (Endo [KVPair]) s KVPair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (KVPair -> Const (Endo [KVPair]) KVPair)
-> t KVPair -> Const (Endo [KVPair]) (t KVPair)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((KVPair -> Const (Endo [KVPair]) KVPair)
-> t KVPair -> Const (Endo [KVPair]) (t KVPair))
-> ((KVPair -> Const (Endo [KVPair]) KVPair)
-> KVPair -> Const (Endo [KVPair]) KVPair)
-> (KVPair -> Const (Endo [KVPair]) KVPair)
-> t KVPair
-> Const (Endo [KVPair]) (t KVPair)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (KVPair -> Const (Endo [KVPair]) KVPair)
-> KVPair -> Const (Endo [KVPair]) KVPair
forall s. Wrapped s => Iso' (Unwrapped s) s
_Unwrapped'
}