{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ouroboros.Consensus.Shelley.Ledger.Query (
BlockQuery (..)
, NonMyopicMemberRewards (..)
, StakeSnapshot (..)
, StakeSnapshots (..)
, decodeShelleyQuery
, decodeShelleyResult
, encodeShelleyQuery
, encodeShelleyResult
) where
import Cardano.Binary (FromCBOR (..), ToCBOR (..), encodeListLen,
enforceSize)
import qualified Cardano.Ledger.Api.State.Query as SL
import Cardano.Ledger.CertState (lookupDepositDState)
import qualified Cardano.Ledger.CertState as SL
import Cardano.Ledger.Coin (Coin)
import Cardano.Ledger.Compactible (Compactible (fromCompact))
import qualified Cardano.Ledger.Conway.Governance as CG
import Cardano.Ledger.Credential (StakeCredential)
import Cardano.Ledger.Keys (KeyHash, KeyRole (..))
import qualified Cardano.Ledger.Shelley.API as SL
import qualified Cardano.Ledger.Shelley.Core as LC
import Cardano.Ledger.Shelley.LedgerState (AccountState)
import qualified Cardano.Ledger.Shelley.RewardProvenance as SL
(RewardProvenance)
import qualified Cardano.Ledger.State as SL
import Cardano.Ledger.UMap (UMap (..), rdReward, umElemDRep,
umElemRDPair, umElemSPool)
import Cardano.Protocol.Crypto (Crypto)
import Codec.CBOR.Decoding (Decoder)
import qualified Codec.CBOR.Decoding as CBOR
import Codec.CBOR.Encoding (Encoding)
import qualified Codec.CBOR.Encoding as CBOR
import Codec.Serialise (decode, encode)
import Control.DeepSeq (NFData)
import Data.Bifunctor (second)
import Data.Kind (Type)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Sequence (Seq (..))
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Type.Equality (apply)
import Data.Typeable (Typeable)
import qualified Data.VMap as VMap
import GHC.Generics (Generic)
import Lens.Micro.Extras (view)
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Config
import Ouroboros.Consensus.HeaderValidation
import Ouroboros.Consensus.Ledger.Basics
import Ouroboros.Consensus.Ledger.Extended
import Ouroboros.Consensus.Ledger.Query
import Ouroboros.Consensus.Ledger.SupportsPeerSelection
import Ouroboros.Consensus.Protocol.Abstract (ChainDepState)
import qualified Ouroboros.Consensus.Shelley.Eras as SE
import Ouroboros.Consensus.Shelley.Ledger.Block
import Ouroboros.Consensus.Shelley.Ledger.Config
import Ouroboros.Consensus.Shelley.Ledger.Ledger
import Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion
(ShelleyNodeToClientVersion (..))
import Ouroboros.Consensus.Shelley.Ledger.PeerSelection ()
import Ouroboros.Consensus.Shelley.Ledger.Query.Types
import Ouroboros.Consensus.Shelley.Protocol.Abstract (ProtoCrypto)
import Ouroboros.Consensus.Util (ShowProxy (..))
import Ouroboros.Network.Block (Serialised (..), decodePoint,
encodePoint, mkSerialised)
import Ouroboros.Network.PeerSelection.LedgerPeers.Type
import Ouroboros.Network.PeerSelection.LedgerPeers.Utils
newtype NonMyopicMemberRewards = NonMyopicMemberRewards {
NonMyopicMemberRewards
-> Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
unNonMyopicMemberRewards ::
Map (Either SL.Coin (SL.Credential 'SL.Staking))
(Map (SL.KeyHash 'SL.StakePool) SL.Coin)
}
deriving stock (Int -> NonMyopicMemberRewards -> ShowS
[NonMyopicMemberRewards] -> ShowS
NonMyopicMemberRewards -> String
(Int -> NonMyopicMemberRewards -> ShowS)
-> (NonMyopicMemberRewards -> String)
-> ([NonMyopicMemberRewards] -> ShowS)
-> Show NonMyopicMemberRewards
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NonMyopicMemberRewards -> ShowS
showsPrec :: Int -> NonMyopicMemberRewards -> ShowS
$cshow :: NonMyopicMemberRewards -> String
show :: NonMyopicMemberRewards -> String
$cshowList :: [NonMyopicMemberRewards] -> ShowS
showList :: [NonMyopicMemberRewards] -> ShowS
Show)
deriving newtype (NonMyopicMemberRewards -> NonMyopicMemberRewards -> Bool
(NonMyopicMemberRewards -> NonMyopicMemberRewards -> Bool)
-> (NonMyopicMemberRewards -> NonMyopicMemberRewards -> Bool)
-> Eq NonMyopicMemberRewards
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NonMyopicMemberRewards -> NonMyopicMemberRewards -> Bool
== :: NonMyopicMemberRewards -> NonMyopicMemberRewards -> Bool
$c/= :: NonMyopicMemberRewards -> NonMyopicMemberRewards -> Bool
/= :: NonMyopicMemberRewards -> NonMyopicMemberRewards -> Bool
Eq, Typeable NonMyopicMemberRewards
Typeable NonMyopicMemberRewards =>
(NonMyopicMemberRewards -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy NonMyopicMemberRewards -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonMyopicMemberRewards] -> Size)
-> ToCBOR NonMyopicMemberRewards
NonMyopicMemberRewards -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonMyopicMemberRewards] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy NonMyopicMemberRewards -> Size
forall a.
Typeable a =>
(a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
$ctoCBOR :: NonMyopicMemberRewards -> Encoding
toCBOR :: NonMyopicMemberRewards -> Encoding
$cencodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy NonMyopicMemberRewards -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy NonMyopicMemberRewards -> Size
$cencodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonMyopicMemberRewards] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonMyopicMemberRewards] -> Size
ToCBOR, Typeable NonMyopicMemberRewards
Typeable NonMyopicMemberRewards =>
(forall s. Decoder s NonMyopicMemberRewards)
-> (Proxy NonMyopicMemberRewards -> Text)
-> FromCBOR NonMyopicMemberRewards
Proxy NonMyopicMemberRewards -> Text
forall s. Decoder s NonMyopicMemberRewards
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
$cfromCBOR :: forall s. Decoder s NonMyopicMemberRewards
fromCBOR :: forall s. Decoder s NonMyopicMemberRewards
$clabel :: Proxy NonMyopicMemberRewards -> Text
label :: Proxy NonMyopicMemberRewards -> Text
FromCBOR)
type Delegations = Map (SL.Credential 'SL.Staking) (SL.KeyHash 'SL.StakePool)
type VoteDelegatees = Map (SL.Credential 'SL.Staking) SL.DRep
{-# DEPRECATED GetProposedPParamsUpdates "Deprecated in ShelleyNodeToClientVersion12" #-}
data instance BlockQuery (ShelleyBlock proto era) :: Type -> Type where
GetLedgerTip :: BlockQuery (ShelleyBlock proto era) (Point (ShelleyBlock proto era))
GetEpochNo :: BlockQuery (ShelleyBlock proto era) EpochNo
GetNonMyopicMemberRewards
:: Set (Either SL.Coin (SL.Credential 'SL.Staking))
-> BlockQuery (ShelleyBlock proto era) NonMyopicMemberRewards
GetCurrentPParams
:: BlockQuery (ShelleyBlock proto era) (LC.PParams era)
GetProposedPParamsUpdates
:: BlockQuery (ShelleyBlock proto era) (SL.ProposedPPUpdates era)
GetStakeDistribution
:: BlockQuery (ShelleyBlock proto era) (PoolDistr (ProtoCrypto proto))
GetUTxOByAddress
:: Set SL.Addr
-> BlockQuery (ShelleyBlock proto era) (SL.UTxO era)
GetUTxOWhole
:: BlockQuery (ShelleyBlock proto era) (SL.UTxO era)
DebugEpochState
:: BlockQuery (ShelleyBlock proto era) (SL.EpochState era)
GetCBOR
:: BlockQuery (ShelleyBlock proto era) result
-> BlockQuery (ShelleyBlock proto era) (Serialised result)
GetFilteredDelegationsAndRewardAccounts
:: Set (SL.Credential 'SL.Staking)
-> BlockQuery (ShelleyBlock proto era)
(Delegations, Map (SL.Credential 'Staking) Coin)
GetGenesisConfig
:: BlockQuery (ShelleyBlock proto era) CompactGenesis
DebugNewEpochState
:: BlockQuery (ShelleyBlock proto era) (SL.NewEpochState era)
DebugChainDepState
:: BlockQuery (ShelleyBlock proto era) (ChainDepState proto)
GetRewardProvenance
:: BlockQuery (ShelleyBlock proto era) SL.RewardProvenance
GetUTxOByTxIn
:: Set SL.TxIn
-> BlockQuery (ShelleyBlock proto era) (SL.UTxO era)
GetStakePools
:: BlockQuery (ShelleyBlock proto era)
(Set (SL.KeyHash 'SL.StakePool))
GetStakePoolParams
:: Set (SL.KeyHash 'SL.StakePool)
-> BlockQuery (ShelleyBlock proto era)
(Map (SL.KeyHash 'SL.StakePool) SL.PoolParams)
GetRewardInfoPools
:: BlockQuery (ShelleyBlock proto era)
(SL.RewardParams,
Map (SL.KeyHash 'SL.StakePool)
(SL.RewardInfoPool))
GetPoolState
:: Maybe (Set (SL.KeyHash 'SL.StakePool))
-> BlockQuery (ShelleyBlock proto era)
(SL.PState era)
GetStakeSnapshots
:: Maybe (Set (SL.KeyHash 'SL.StakePool))
-> BlockQuery (ShelleyBlock proto era)
StakeSnapshots
GetPoolDistr
:: Maybe (Set (SL.KeyHash 'SL.StakePool))
-> BlockQuery (ShelleyBlock proto era)
(PoolDistr (ProtoCrypto proto))
GetStakeDelegDeposits
:: Set StakeCredential
-> BlockQuery (ShelleyBlock proto era)
(Map StakeCredential Coin)
GetConstitution
:: CG.ConwayEraGov era
=> BlockQuery (ShelleyBlock proto era) (CG.Constitution era)
GetGovState
:: BlockQuery (ShelleyBlock proto era) (LC.GovState era)
GetDRepState
:: CG.ConwayEraGov era
=> Set (SL.Credential 'DRepRole)
-> BlockQuery (ShelleyBlock proto era)
(Map
(SL.Credential 'DRepRole)
SL.DRepState
)
GetDRepStakeDistr
:: CG.ConwayEraGov era
=> Set SL.DRep
-> BlockQuery (ShelleyBlock proto era) (Map SL.DRep Coin)
:: CG.ConwayEraGov era
=> Set (SL.Credential 'ColdCommitteeRole)
-> Set (SL.Credential 'HotCommitteeRole)
-> Set SL.MemberStatus
-> BlockQuery (ShelleyBlock proto era) SL.CommitteeMembersState
GetFilteredVoteDelegatees
:: CG.ConwayEraGov era
=> Set (SL.Credential 'SL.Staking)
-> BlockQuery (ShelleyBlock proto era) VoteDelegatees
GetAccountState
:: BlockQuery (ShelleyBlock proto era) AccountState
GetSPOStakeDistr
:: CG.ConwayEraGov era
=> Set (KeyHash 'StakePool)
-> BlockQuery (ShelleyBlock proto era) (Map (KeyHash 'StakePool) Coin)
GetProposals
:: CG.ConwayEraGov era
=> Set CG.GovActionId
-> BlockQuery (ShelleyBlock proto era) (Seq (CG.GovActionState era))
GetRatifyState
:: CG.ConwayEraGov era
=> BlockQuery (ShelleyBlock proto era) (CG.RatifyState era)
GetFuturePParams
:: BlockQuery (ShelleyBlock proto era) (Maybe (LC.PParams era))
GetBigLedgerPeerSnapshot
:: BlockQuery (ShelleyBlock proto era) LedgerPeerSnapshot
QueryStakePoolDefaultVote
:: CG.ConwayEraGov era
=> KeyHash 'StakePool
-> BlockQuery (ShelleyBlock proto era) CG.DefaultVote
instance (Typeable era, Typeable proto)
=> ShowProxy (BlockQuery (ShelleyBlock proto era)) where
instance
( ShelleyCompatible proto era
, ProtoCrypto proto ~ crypto
, Crypto crypto
) =>
BlockSupportsLedgerQuery (ShelleyBlock proto era)
where
answerBlockQuery :: forall result.
ExtLedgerCfg (ShelleyBlock proto era)
-> BlockQuery (ShelleyBlock proto era) result
-> ExtLedgerState (ShelleyBlock proto era)
-> result
answerBlockQuery ExtLedgerCfg (ShelleyBlock proto era)
cfg BlockQuery (ShelleyBlock proto era) result
query ExtLedgerState (ShelleyBlock proto era)
ext =
case BlockQuery (ShelleyBlock proto era) result
query of
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetLedgerTip ->
LedgerState (ShelleyBlock proto era)
-> Point (ShelleyBlock proto era)
forall proto era.
LedgerState (ShelleyBlock proto era)
-> Point (ShelleyBlock proto era)
shelleyLedgerTipPoint LedgerState (ShelleyBlock proto era)
lst
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetEpochNo ->
NewEpochState era -> EpochNo
forall era. NewEpochState era -> EpochNo
SL.nesEL NewEpochState era
st
GetNonMyopicMemberRewards Set (Either Coin (Credential 'Staking))
creds ->
Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
-> NonMyopicMemberRewards
NonMyopicMemberRewards (Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
-> NonMyopicMemberRewards)
-> Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
-> NonMyopicMemberRewards
forall a b. (a -> b) -> a -> b
$
Globals
-> NewEpochState era
-> Set (Either Coin (Credential 'Staking))
-> Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
forall era.
(EraGov era, EraStake era, EraCertState era) =>
Globals
-> NewEpochState era
-> Set (Either Coin (Credential 'Staking))
-> Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
SL.getNonMyopicMemberRewards Globals
globals NewEpochState era
st Set (Either Coin (Credential 'Staking))
creds
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetCurrentPParams ->
NewEpochState era -> PParams era
forall era. EraGov era => NewEpochState era -> PParams era
getPParams NewEpochState era
st
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetProposedPParamsUpdates ->
Map (KeyHash 'Genesis) (PParamsUpdate era) -> ProposedPPUpdates era
forall era.
Map (KeyHash 'Genesis) (PParamsUpdate era) -> ProposedPPUpdates era
SL.ProposedPPUpdates Map (KeyHash 'Genesis) (PParamsUpdate era)
forall k a. Map k a
Map.empty
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakeDistribution ->
PoolDistr -> PoolDistr crypto
forall c. PoolDistr -> PoolDistr c
fromLedgerPoolDistr (PoolDistr -> PoolDistr crypto) -> PoolDistr -> PoolDistr crypto
forall a b. (a -> b) -> a -> b
$ Globals -> NewEpochState era -> PoolDistr
forall era.
(EraGov era, EraStake era, EraCertState era) =>
Globals -> NewEpochState era -> PoolDistr
SL.poolsByTotalStakeFraction Globals
globals NewEpochState era
st
GetUTxOByAddress Set Addr
addrs ->
NewEpochState era -> Set Addr -> UTxO era
forall era.
EraTxOut era =>
NewEpochState era -> Set Addr -> UTxO era
SL.getFilteredUTxO NewEpochState era
st Set Addr
addrs
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetUTxOWhole ->
NewEpochState era -> UTxO era
forall era. NewEpochState era -> UTxO era
SL.getUTxO NewEpochState era
st
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugEpochState ->
NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
getEpochState NewEpochState era
st
GetCBOR BlockQuery (ShelleyBlock proto era) result
query' ->
(result -> Encoding) -> result -> Serialised result
forall a. (a -> Encoding) -> a -> Serialised a
mkSerialised (ShelleyNodeToClientVersion
-> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding
forall proto era result.
ShelleyCompatible proto era =>
ShelleyNodeToClientVersion
-> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding
encodeShelleyResult ShelleyNodeToClientVersion
forall a. Bounded a => a
maxBound BlockQuery (ShelleyBlock proto era) result
query') (result -> Serialised result) -> result -> Serialised result
forall a b. (a -> b) -> a -> b
$
ExtLedgerCfg (ShelleyBlock proto era)
-> BlockQuery (ShelleyBlock proto era) result
-> ExtLedgerState (ShelleyBlock proto era)
-> result
forall result.
ExtLedgerCfg (ShelleyBlock proto era)
-> BlockQuery (ShelleyBlock proto era) result
-> ExtLedgerState (ShelleyBlock proto era)
-> result
forall blk result.
BlockSupportsLedgerQuery blk =>
ExtLedgerCfg blk
-> BlockQuery blk result -> ExtLedgerState blk -> result
answerBlockQuery ExtLedgerCfg (ShelleyBlock proto era)
cfg BlockQuery (ShelleyBlock proto era) result
query' ExtLedgerState (ShelleyBlock proto era)
ext
GetFilteredDelegationsAndRewardAccounts Set (Credential 'Staking)
creds ->
NewEpochState era
-> Set (Credential 'Staking)
-> (Delegations, Map (Credential 'Staking) Coin)
forall era.
EraCertState era =>
NewEpochState era
-> Set (Credential 'Staking)
-> (Delegations, Map (Credential 'Staking) Coin)
getFilteredDelegationsAndRewardAccounts NewEpochState era
st Set (Credential 'Staking)
creds
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGenesisConfig ->
ShelleyLedgerConfig era -> CompactGenesis
forall era. ShelleyLedgerConfig era -> CompactGenesis
shelleyLedgerCompactGenesis LedgerConfig (ShelleyBlock proto era)
ShelleyLedgerConfig era
lcfg
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugNewEpochState ->
result
NewEpochState era
st
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugChainDepState ->
HeaderState (ShelleyBlock proto era)
-> ChainDepState (BlockProtocol (ShelleyBlock proto era))
forall blk. HeaderState blk -> ChainDepState (BlockProtocol blk)
headerStateChainDep HeaderState (ShelleyBlock proto era)
hst
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardProvenance ->
(RewardUpdate, RewardProvenance) -> RewardProvenance
forall a b. (a, b) -> b
snd ((RewardUpdate, RewardProvenance) -> RewardProvenance)
-> (RewardUpdate, RewardProvenance) -> RewardProvenance
forall a b. (a -> b) -> a -> b
$ Globals -> NewEpochState era -> (RewardUpdate, RewardProvenance)
forall era.
(EraGov era, EraCertState era) =>
Globals -> NewEpochState era -> (RewardUpdate, RewardProvenance)
SL.getRewardProvenance Globals
globals NewEpochState era
st
GetUTxOByTxIn Set TxIn
txins ->
NewEpochState era -> Set TxIn -> UTxO era
forall era. NewEpochState era -> Set TxIn -> UTxO era
SL.getUTxOSubset NewEpochState era
st Set TxIn
txins
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakePools ->
NewEpochState era -> Set (KeyHash 'StakePool)
forall era.
EraCertState era =>
NewEpochState era -> Set (KeyHash 'StakePool)
SL.getPools NewEpochState era
st
GetStakePoolParams Set (KeyHash 'StakePool)
poolids ->
NewEpochState era
-> Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) PoolParams
forall era.
EraCertState era =>
NewEpochState era
-> Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) PoolParams
SL.getPoolParameters NewEpochState era
st Set (KeyHash 'StakePool)
poolids
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardInfoPools ->
Globals
-> NewEpochState era
-> (RewardParams, Map (KeyHash 'StakePool) RewardInfoPool)
forall era.
(EraGov era, EraStake era, EraCertState era) =>
Globals
-> NewEpochState era
-> (RewardParams, Map (KeyHash 'StakePool) RewardInfoPool)
SL.getRewardInfoPools Globals
globals NewEpochState era
st
GetPoolState Maybe (Set (KeyHash 'StakePool))
mPoolIds ->
let certPState :: PState era
certPState = Getting (PState era) (CertState era) (PState era)
-> CertState era -> PState era
forall a s. Getting a s a -> s -> a
view Getting (PState era) (CertState era) (PState era)
forall era. EraCertState era => Lens' (CertState era) (PState era)
Lens' (CertState era) (PState era)
SL.certPStateL (CertState era -> PState era)
-> (NewEpochState era -> CertState era)
-> NewEpochState era
-> PState era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState era -> CertState era
forall era. LedgerState era -> CertState era
SL.lsCertState (LedgerState era -> CertState era)
-> (NewEpochState era -> LedgerState era)
-> NewEpochState era
-> CertState era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EpochState era -> LedgerState era
forall era. EpochState era -> LedgerState era
SL.esLState (EpochState era -> LedgerState era)
-> (NewEpochState era -> EpochState era)
-> NewEpochState era
-> LedgerState era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
SL.nesEs (NewEpochState era -> PState era)
-> NewEpochState era -> PState era
forall a b. (a -> b) -> a -> b
$ NewEpochState era
st in
case Maybe (Set (KeyHash 'StakePool))
mPoolIds of
Just Set (KeyHash 'StakePool)
poolIds ->
SL.PState
{ psStakePoolParams :: Map (KeyHash 'StakePool) PoolParams
SL.psStakePoolParams =
Map (KeyHash 'StakePool) PoolParams
-> Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) PoolParams
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys (PState era -> Map (KeyHash 'StakePool) PoolParams
forall era. PState era -> Map (KeyHash 'StakePool) PoolParams
SL.psStakePoolParams PState era
certPState) Set (KeyHash 'StakePool)
poolIds
, psFutureStakePoolParams :: Map (KeyHash 'StakePool) PoolParams
SL.psFutureStakePoolParams =
Map (KeyHash 'StakePool) PoolParams
-> Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) PoolParams
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys (PState era -> Map (KeyHash 'StakePool) PoolParams
forall era. PState era -> Map (KeyHash 'StakePool) PoolParams
SL.psFutureStakePoolParams PState era
certPState) Set (KeyHash 'StakePool)
poolIds
, psRetiring :: Map (KeyHash 'StakePool) EpochNo
SL.psRetiring = Map (KeyHash 'StakePool) EpochNo
-> Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) EpochNo
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys (PState era -> Map (KeyHash 'StakePool) EpochNo
forall era. PState era -> Map (KeyHash 'StakePool) EpochNo
SL.psRetiring PState era
certPState) Set (KeyHash 'StakePool)
poolIds
, psDeposits :: Map (KeyHash 'StakePool) Coin
SL.psDeposits = Map (KeyHash 'StakePool) Coin
-> Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) Coin
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys (PState era -> Map (KeyHash 'StakePool) Coin
forall era. PState era -> Map (KeyHash 'StakePool) Coin
SL.psDeposits PState era
certPState) Set (KeyHash 'StakePool)
poolIds
}
Maybe (Set (KeyHash 'StakePool))
Nothing -> result
PState era
certPState
GetStakeSnapshots Maybe (Set (KeyHash 'StakePool))
mPoolIds ->
let SL.SnapShots
{ SnapShot
ssStakeMark :: SnapShot
$sel:ssStakeMark:SnapShots :: SnapShots -> SnapShot
SL.ssStakeMark
, SnapShot
ssStakeSet :: SnapShot
$sel:ssStakeSet:SnapShots :: SnapShots -> SnapShot
SL.ssStakeSet
, SnapShot
ssStakeGo :: SnapShot
$sel:ssStakeGo:SnapShots :: SnapShots -> SnapShot
SL.ssStakeGo
} = EpochState era -> SnapShots
forall era. EpochState era -> SnapShots
SL.esSnapshots (EpochState era -> SnapShots)
-> (NewEpochState era -> EpochState era)
-> NewEpochState era
-> SnapShots
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
SL.nesEs (NewEpochState era -> SnapShots) -> NewEpochState era -> SnapShots
forall a b. (a -> b) -> a -> b
$ NewEpochState era
st
totalMarkByPoolId :: Map (KeyHash 'StakePool) Coin
totalMarkByPoolId :: Map (KeyHash 'StakePool) Coin
totalMarkByPoolId = VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
-> Stake -> Map (KeyHash 'StakePool) Coin
SL.sumStakePerPool (SnapShot -> VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
SL.ssDelegations SnapShot
ssStakeMark) (SnapShot -> Stake
SL.ssStake SnapShot
ssStakeMark)
totalSetByPoolId :: Map (KeyHash 'StakePool) Coin
totalSetByPoolId :: Map (KeyHash 'StakePool) Coin
totalSetByPoolId = VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
-> Stake -> Map (KeyHash 'StakePool) Coin
SL.sumStakePerPool (SnapShot -> VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
SL.ssDelegations SnapShot
ssStakeSet) (SnapShot -> Stake
SL.ssStake SnapShot
ssStakeSet)
totalGoByPoolId :: Map (KeyHash 'StakePool) Coin
totalGoByPoolId :: Map (KeyHash 'StakePool) Coin
totalGoByPoolId = VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
-> Stake -> Map (KeyHash 'StakePool) Coin
SL.sumStakePerPool (SnapShot -> VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
SL.ssDelegations SnapShot
ssStakeGo) (SnapShot -> Stake
SL.ssStake SnapShot
ssStakeGo)
getPoolStakes :: Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) StakeSnapshot
getPoolStakes :: Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) StakeSnapshot
getPoolStakes Set (KeyHash 'StakePool)
poolIds = (KeyHash 'StakePool -> StakeSnapshot)
-> Set (KeyHash 'StakePool)
-> Map (KeyHash 'StakePool) StakeSnapshot
forall k a. (k -> a) -> Set k -> Map k a
Map.fromSet KeyHash 'StakePool -> StakeSnapshot
mkStakeSnapshot Set (KeyHash 'StakePool)
poolIds
where mkStakeSnapshot :: KeyHash 'StakePool -> StakeSnapshot
mkStakeSnapshot KeyHash 'StakePool
poolId = StakeSnapshot
{ ssMarkPool :: Coin
ssMarkPool = Coin -> KeyHash 'StakePool -> Map (KeyHash 'StakePool) Coin -> Coin
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault Coin
forall a. Monoid a => a
mempty KeyHash 'StakePool
poolId Map (KeyHash 'StakePool) Coin
totalMarkByPoolId
, ssSetPool :: Coin
ssSetPool = Coin -> KeyHash 'StakePool -> Map (KeyHash 'StakePool) Coin -> Coin
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault Coin
forall a. Monoid a => a
mempty KeyHash 'StakePool
poolId Map (KeyHash 'StakePool) Coin
totalSetByPoolId
, ssGoPool :: Coin
ssGoPool = Coin -> KeyHash 'StakePool -> Map (KeyHash 'StakePool) Coin -> Coin
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault Coin
forall a. Monoid a => a
mempty KeyHash 'StakePool
poolId Map (KeyHash 'StakePool) Coin
totalGoByPoolId
}
getAllStake :: SL.SnapShot -> SL.Coin
getAllStake :: SnapShot -> Coin
getAllStake (SL.SnapShot Stake
stake VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
_ VMap VB VB (KeyHash 'StakePool) PoolParams
_) = (CompactForm Coin -> Coin)
-> VMap VB VP (Credential 'Staking) (CompactForm Coin) -> Coin
forall (vv :: * -> *) v m (kv :: * -> *) k.
(Vector vv v, Monoid m) =>
(v -> m) -> VMap kv vv k v -> m
VMap.foldMap CompactForm Coin -> Coin
forall a. Compactible a => CompactForm a -> a
fromCompact (Stake -> VMap VB VP (Credential 'Staking) (CompactForm Coin)
SL.unStake Stake
stake)
in
case Maybe (Set (KeyHash 'StakePool))
mPoolIds of
Maybe (Set (KeyHash 'StakePool))
Nothing ->
let poolIds :: Set (KeyHash 'StakePool)
poolIds = [KeyHash 'StakePool] -> Set (KeyHash 'StakePool)
forall a. Ord a => [a] -> Set a
Set.fromList ([KeyHash 'StakePool] -> Set (KeyHash 'StakePool))
-> [KeyHash 'StakePool] -> Set (KeyHash 'StakePool)
forall a b. (a -> b) -> a -> b
$ [[KeyHash 'StakePool]] -> [KeyHash 'StakePool]
forall a. Monoid a => [a] -> a
mconcat
[ VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
-> [KeyHash 'StakePool]
forall (vv :: * -> *) v (kv :: * -> *) k.
Vector vv v =>
VMap kv vv k v -> [v]
VMap.elems (SnapShot -> VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
SL.ssDelegations SnapShot
ssStakeMark)
, VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
-> [KeyHash 'StakePool]
forall (vv :: * -> *) v (kv :: * -> *) k.
Vector vv v =>
VMap kv vv k v -> [v]
VMap.elems (SnapShot -> VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
SL.ssDelegations SnapShot
ssStakeSet)
, VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
-> [KeyHash 'StakePool]
forall (vv :: * -> *) v (kv :: * -> *) k.
Vector vv v =>
VMap kv vv k v -> [v]
VMap.elems (SnapShot -> VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
SL.ssDelegations SnapShot
ssStakeGo)
]
in
StakeSnapshots
{ ssStakeSnapshots :: Map (KeyHash 'StakePool) StakeSnapshot
ssStakeSnapshots = Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) StakeSnapshot
getPoolStakes Set (KeyHash 'StakePool)
poolIds
, ssMarkTotal :: Coin
ssMarkTotal = SnapShot -> Coin
getAllStake SnapShot
ssStakeMark
, ssSetTotal :: Coin
ssSetTotal = SnapShot -> Coin
getAllStake SnapShot
ssStakeSet
, ssGoTotal :: Coin
ssGoTotal = SnapShot -> Coin
getAllStake SnapShot
ssStakeGo
}
Just Set (KeyHash 'StakePool)
poolIds ->
StakeSnapshots
{ ssStakeSnapshots :: Map (KeyHash 'StakePool) StakeSnapshot
ssStakeSnapshots = Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) StakeSnapshot
getPoolStakes Set (KeyHash 'StakePool)
poolIds
, ssMarkTotal :: Coin
ssMarkTotal = SnapShot -> Coin
getAllStake SnapShot
ssStakeMark
, ssSetTotal :: Coin
ssSetTotal = SnapShot -> Coin
getAllStake SnapShot
ssStakeSet
, ssGoTotal :: Coin
ssGoTotal = SnapShot -> Coin
getAllStake SnapShot
ssStakeGo
}
GetPoolDistr Maybe (Set (KeyHash 'StakePool))
mPoolIds ->
let stakeSet :: SnapShot
stakeSet = SnapShots -> SnapShot
SL.ssStakeSet (SnapShots -> SnapShot)
-> (EpochState era -> SnapShots) -> EpochState era -> SnapShot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EpochState era -> SnapShots
forall era. EpochState era -> SnapShots
SL.esSnapshots (EpochState era -> SnapShot) -> EpochState era -> SnapShot
forall a b. (a -> b) -> a -> b
$ NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
getEpochState NewEpochState era
st in
PoolDistr -> PoolDistr crypto
forall c. PoolDistr -> PoolDistr c
fromLedgerPoolDistr (PoolDistr -> PoolDistr crypto) -> PoolDistr -> PoolDistr crypto
forall a b. (a -> b) -> a -> b
$
(KeyHash 'StakePool -> Bool) -> SnapShot -> PoolDistr
SL.calculatePoolDistr' ((KeyHash 'StakePool -> Bool)
-> (Set (KeyHash 'StakePool) -> KeyHash 'StakePool -> Bool)
-> Maybe (Set (KeyHash 'StakePool))
-> KeyHash 'StakePool
-> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Bool -> KeyHash 'StakePool -> Bool
forall a b. a -> b -> a
const Bool
True) ((KeyHash 'StakePool -> Set (KeyHash 'StakePool) -> Bool)
-> Set (KeyHash 'StakePool) -> KeyHash 'StakePool -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip KeyHash 'StakePool -> Set (KeyHash 'StakePool) -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member) Maybe (Set (KeyHash 'StakePool))
mPoolIds) SnapShot
stakeSet
GetStakeDelegDeposits Set (Credential 'Staking)
stakeCreds ->
let lookupDeposit :: Credential 'Staking -> Maybe Coin
lookupDeposit =
DState era -> Credential 'Staking -> Maybe Coin
forall era. DState era -> Credential 'Staking -> Maybe Coin
lookupDepositDState (Getting (DState era) (CertState era) (DState era)
-> CertState era -> DState era
forall a s. Getting a s a -> s -> a
view Getting (DState era) (CertState era) (DState era)
forall era. EraCertState era => Lens' (CertState era) (DState era)
Lens' (CertState era) (DState era)
SL.certDStateL (CertState era -> DState era) -> CertState era -> DState era
forall a b. (a -> b) -> a -> b
$ LedgerState era -> CertState era
forall era. LedgerState era -> CertState era
SL.lsCertState (LedgerState era -> CertState era)
-> LedgerState era -> CertState era
forall a b. (a -> b) -> a -> b
$ EpochState era -> LedgerState era
forall era. EpochState era -> LedgerState era
SL.esLState (EpochState era -> LedgerState era)
-> EpochState era -> LedgerState era
forall a b. (a -> b) -> a -> b
$ NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
SL.nesEs NewEpochState era
st)
lookupInsert :: Map (Credential 'Staking) Coin
-> Credential 'Staking -> Map (Credential 'Staking) Coin
lookupInsert Map (Credential 'Staking) Coin
acc Credential 'Staking
cred =
case Credential 'Staking -> Maybe Coin
lookupDeposit Credential 'Staking
cred of
Maybe Coin
Nothing -> Map (Credential 'Staking) Coin
acc
Just Coin
deposit -> Credential 'Staking
-> Coin
-> Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) Coin
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Credential 'Staking
cred Coin
deposit Map (Credential 'Staking) Coin
acc
in (result -> Credential 'Staking -> result)
-> result -> Set (Credential 'Staking) -> result
forall a b. (a -> b -> a) -> a -> Set b -> a
Set.foldl' result -> Credential 'Staking -> result
Map (Credential 'Staking) Coin
-> Credential 'Staking -> Map (Credential 'Staking) Coin
lookupInsert result
Map (Credential 'Staking) Coin
forall k a. Map k a
Map.empty Set (Credential 'Staking)
stakeCreds
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetConstitution ->
NewEpochState era -> Constitution era
forall era.
ConwayEraGov era =>
NewEpochState era -> Constitution era
SL.queryConstitution NewEpochState era
st
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGovState ->
NewEpochState era -> GovState era
forall era. NewEpochState era -> GovState era
SL.queryGovState NewEpochState era
st
GetDRepState Set (Credential 'DRepRole)
drepCreds ->
NewEpochState era
-> Set (Credential 'DRepRole)
-> Map (Credential 'DRepRole) DRepState
forall era.
EraCertState era =>
NewEpochState era
-> Set (Credential 'DRepRole)
-> Map (Credential 'DRepRole) DRepState
SL.queryDRepState NewEpochState era
st Set (Credential 'DRepRole)
drepCreds
GetDRepStakeDistr Set DRep
dreps ->
NewEpochState era -> Set DRep -> Map DRep Coin
forall era.
ConwayEraGov era =>
NewEpochState era -> Set DRep -> Map DRep Coin
SL.queryDRepStakeDistr NewEpochState era
st Set DRep
dreps
GetCommitteeMembersState Set (Credential 'ColdCommitteeRole)
coldCreds Set (Credential 'HotCommitteeRole)
hotCreds Set MemberStatus
statuses ->
Set (Credential 'ColdCommitteeRole)
-> Set (Credential 'HotCommitteeRole)
-> Set MemberStatus
-> NewEpochState era
-> CommitteeMembersState
forall era.
(ConwayEraGov era, EraCertState era) =>
Set (Credential 'ColdCommitteeRole)
-> Set (Credential 'HotCommitteeRole)
-> Set MemberStatus
-> NewEpochState era
-> CommitteeMembersState
SL.queryCommitteeMembersState Set (Credential 'ColdCommitteeRole)
coldCreds Set (Credential 'HotCommitteeRole)
hotCreds Set MemberStatus
statuses NewEpochState era
st
GetFilteredVoteDelegatees Set (Credential 'Staking)
stakeCreds ->
NewEpochState era
-> Set (Credential 'Staking) -> Map (Credential 'Staking) DRep
forall era.
EraCertState era =>
NewEpochState era
-> Set (Credential 'Staking) -> Map (Credential 'Staking) DRep
getFilteredVoteDelegatees NewEpochState era
st Set (Credential 'Staking)
stakeCreds
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetAccountState ->
NewEpochState era -> AccountState
forall era. NewEpochState era -> AccountState
SL.queryAccountState NewEpochState era
st
GetSPOStakeDistr Set (KeyHash 'StakePool)
keys ->
NewEpochState era
-> Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) Coin
forall era.
ConwayEraGov era =>
NewEpochState era
-> Set (KeyHash 'StakePool) -> Map (KeyHash 'StakePool) Coin
SL.querySPOStakeDistr NewEpochState era
st Set (KeyHash 'StakePool)
keys
GetProposals Set GovActionId
gids ->
NewEpochState era -> Set GovActionId -> Seq (GovActionState era)
forall era.
ConwayEraGov era =>
NewEpochState era -> Set GovActionId -> Seq (GovActionState era)
SL.queryProposals NewEpochState era
st Set GovActionId
gids
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRatifyState ->
NewEpochState era -> RatifyState era
forall era.
ConwayEraGov era =>
NewEpochState era -> RatifyState era
SL.queryRatifyState NewEpochState era
st
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetFuturePParams ->
NewEpochState era -> Maybe (PParams era)
forall era. EraGov era => NewEpochState era -> Maybe (PParams era)
SL.queryFuturePParams NewEpochState era
st
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetBigLedgerPeerSnapshot ->
let slot :: WithOrigin SlotNo
slot = LedgerState (ShelleyBlock proto era) -> WithOrigin SlotNo
forall l. GetTip l => l -> WithOrigin SlotNo
getTipSlot LedgerState (ShelleyBlock proto era)
lst
ledgerPeers :: [(PoolStake, NonEmpty RelayAccessPoint)]
ledgerPeers = (NonEmpty StakePoolRelay -> NonEmpty RelayAccessPoint)
-> (PoolStake, NonEmpty StakePoolRelay)
-> (PoolStake, NonEmpty RelayAccessPoint)
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second ((StakePoolRelay -> RelayAccessPoint)
-> NonEmpty StakePoolRelay -> NonEmpty RelayAccessPoint
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StakePoolRelay -> RelayAccessPoint
stakePoolRelayAccessPoint) ((PoolStake, NonEmpty StakePoolRelay)
-> (PoolStake, NonEmpty RelayAccessPoint))
-> [(PoolStake, NonEmpty StakePoolRelay)]
-> [(PoolStake, NonEmpty RelayAccessPoint)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LedgerState (ShelleyBlock proto era)
-> [(PoolStake, NonEmpty StakePoolRelay)]
forall blk.
LedgerSupportsPeerSelection blk =>
LedgerState blk -> [(PoolStake, NonEmpty StakePoolRelay)]
getPeers LedgerState (ShelleyBlock proto era)
lst
bigLedgerPeers :: [(AccPoolStake, (PoolStake, NonEmpty RelayAccessPoint))]
bigLedgerPeers = [(PoolStake, NonEmpty RelayAccessPoint)]
-> [(AccPoolStake, (PoolStake, NonEmpty RelayAccessPoint))]
accumulateBigLedgerStake [(PoolStake, NonEmpty RelayAccessPoint)]
ledgerPeers
in (WithOrigin SlotNo,
[(AccPoolStake, (PoolStake, NonEmpty RelayAccessPoint))])
-> LedgerPeerSnapshot
LedgerPeerSnapshot (WithOrigin SlotNo
slot, [(AccPoolStake, (PoolStake, NonEmpty RelayAccessPoint))]
bigLedgerPeers)
QueryStakePoolDefaultVote KeyHash 'StakePool
stakePool ->
NewEpochState era -> KeyHash 'StakePool -> DefaultVote
forall era.
EraCertState era =>
NewEpochState era -> KeyHash 'StakePool -> DefaultVote
SL.queryStakePoolDefaultVote NewEpochState era
st KeyHash 'StakePool
stakePool
where
lcfg :: LedgerConfig (ShelleyBlock proto era)
lcfg = TopLevelConfig (ShelleyBlock proto era)
-> LedgerConfig (ShelleyBlock proto era)
forall blk. TopLevelConfig blk -> LedgerConfig blk
configLedger (TopLevelConfig (ShelleyBlock proto era)
-> LedgerConfig (ShelleyBlock proto era))
-> TopLevelConfig (ShelleyBlock proto era)
-> LedgerConfig (ShelleyBlock proto era)
forall a b. (a -> b) -> a -> b
$ ExtLedgerCfg (ShelleyBlock proto era)
-> TopLevelConfig (ShelleyBlock proto era)
forall blk. ExtLedgerCfg blk -> TopLevelConfig blk
getExtLedgerCfg ExtLedgerCfg (ShelleyBlock proto era)
cfg
globals :: Globals
globals = ShelleyLedgerConfig era -> Globals
forall era. ShelleyLedgerConfig era -> Globals
shelleyLedgerGlobals LedgerConfig (ShelleyBlock proto era)
ShelleyLedgerConfig era
lcfg
lst :: LedgerState (ShelleyBlock proto era)
lst = ExtLedgerState (ShelleyBlock proto era)
-> LedgerState (ShelleyBlock proto era)
forall blk. ExtLedgerState blk -> LedgerState blk
ledgerState ExtLedgerState (ShelleyBlock proto era)
ext
hst :: HeaderState (ShelleyBlock proto era)
hst = ExtLedgerState (ShelleyBlock proto era)
-> HeaderState (ShelleyBlock proto era)
forall blk. ExtLedgerState blk -> HeaderState blk
headerState ExtLedgerState (ShelleyBlock proto era)
ext
st :: NewEpochState era
st = LedgerState (ShelleyBlock proto era) -> NewEpochState era
forall proto era.
LedgerState (ShelleyBlock proto era) -> NewEpochState era
shelleyLedgerState LedgerState (ShelleyBlock proto era)
lst
blockQueryIsSupportedOnVersion :: forall result.
BlockQuery (ShelleyBlock proto era) result
-> BlockNodeToClientVersion (ShelleyBlock proto era) -> Bool
blockQueryIsSupportedOnVersion = \case
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetLedgerTip -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetEpochNo -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
GetNonMyopicMemberRewards {} -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetCurrentPParams -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetProposedPParamsUpdates -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
< ShelleyNodeToClientVersion
v12)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakeDistribution -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
GetUTxOByAddress {} -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetUTxOWhole -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugEpochState -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
GetCBOR BlockQuery (ShelleyBlock proto era) result
q -> BlockQuery (ShelleyBlock proto era) result
-> BlockNodeToClientVersion (ShelleyBlock proto era) -> Bool
forall blk result.
BlockSupportsLedgerQuery blk =>
BlockQuery blk result -> BlockNodeToClientVersion blk -> Bool
forall result.
BlockQuery (ShelleyBlock proto era) result
-> BlockNodeToClientVersion (ShelleyBlock proto era) -> Bool
blockQueryIsSupportedOnVersion BlockQuery (ShelleyBlock proto era) result
q
GetFilteredDelegationsAndRewardAccounts {} -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGenesisConfig -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugNewEpochState -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugChainDepState -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardProvenance -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
GetUTxOByTxIn {} -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakePools -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
GetStakePoolParams {} -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardInfoPools -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
GetPoolState {} -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
GetStakeSnapshots {} -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
GetPoolDistr {} -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
GetStakeDelegDeposits {} -> Bool -> ShelleyNodeToClientVersion -> Bool
forall a b. a -> b -> a
const Bool
True
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetConstitution -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v8)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGovState -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v8)
GetDRepState {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v8)
GetDRepStakeDistr {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v8)
GetCommitteeMembersState {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v8)
GetFilteredVoteDelegatees {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v8)
GetAccountState {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v8)
GetSPOStakeDistr {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v8)
GetProposals {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v9)
GetRatifyState {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v9)
GetFuturePParams {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v10)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetBigLedgerPeerSnapshot -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v11)
QueryStakePoolDefaultVote {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v12)
where
v8 :: ShelleyNodeToClientVersion
v8 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion8
v9 :: ShelleyNodeToClientVersion
v9 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion9
v10 :: ShelleyNodeToClientVersion
v10 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion10
v11 :: ShelleyNodeToClientVersion
v11 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion11
v12 :: ShelleyNodeToClientVersion
v12 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion12
instance SameDepIndex (BlockQuery (ShelleyBlock proto era)) where
sameDepIndex :: forall a b.
BlockQuery (ShelleyBlock proto era) a
-> BlockQuery (ShelleyBlock proto era) b -> Maybe (a :~: b)
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetLedgerTip BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetLedgerTip
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetLedgerTip BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetEpochNo BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetEpochNo
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetEpochNo BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetNonMyopicMemberRewards Set (Either Coin (Credential 'Staking))
creds) (GetNonMyopicMemberRewards Set (Either Coin (Credential 'Staking))
creds')
| Set (Either Coin (Credential 'Staking))
creds Set (Either Coin (Credential 'Staking))
-> Set (Either Coin (Credential 'Staking)) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (Either Coin (Credential 'Staking))
creds'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetNonMyopicMemberRewards Set (Either Coin (Credential 'Staking))
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetCurrentPParams BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetCurrentPParams
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetCurrentPParams BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetProposedPParamsUpdates BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetProposedPParamsUpdates
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetProposedPParamsUpdates BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetStakeDistribution BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetStakeDistribution
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetStakeDistribution BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetUTxOByAddress Set Addr
addrs) (GetUTxOByAddress Set Addr
addrs')
| Set Addr
addrs Set Addr -> Set Addr -> Bool
forall a. Eq a => a -> a -> Bool
== Set Addr
addrs'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetUTxOByAddress Set Addr
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetUTxOWhole BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetUTxOWhole
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetUTxOWhole BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
DebugEpochState BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
DebugEpochState
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
DebugEpochState BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetCBOR BlockQuery (ShelleyBlock proto era) result
q) (GetCBOR BlockQuery (ShelleyBlock proto era) result
q')
= (Serialised :~: Serialised)
-> (result :~: result) -> Serialised result :~: Serialised result
forall {k1} {k2} (f :: k1 -> k2) (g :: k1 -> k2) (a :: k1)
(b :: k1).
(f :~: g) -> (a :~: b) -> f a :~: g b
apply Serialised :~: Serialised
forall {k} (a :: k). a :~: a
Refl ((result :~: result) -> a :~: b)
-> Maybe (result :~: result) -> Maybe (a :~: b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BlockQuery (ShelleyBlock proto era) result
-> BlockQuery (ShelleyBlock proto era) result
-> Maybe (result :~: result)
forall a b.
BlockQuery (ShelleyBlock proto era) a
-> BlockQuery (ShelleyBlock proto era) b -> Maybe (a :~: b)
forall (f :: * -> *) a b.
SameDepIndex f =>
f a -> f b -> Maybe (a :~: b)
sameDepIndex BlockQuery (ShelleyBlock proto era) result
q BlockQuery (ShelleyBlock proto era) result
q'
sameDepIndex (GetCBOR BlockQuery (ShelleyBlock proto era) result
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetFilteredDelegationsAndRewardAccounts Set (Credential 'Staking)
creds)
(GetFilteredDelegationsAndRewardAccounts Set (Credential 'Staking)
creds')
| Set (Credential 'Staking)
creds Set (Credential 'Staking) -> Set (Credential 'Staking) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (Credential 'Staking)
creds'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetFilteredDelegationsAndRewardAccounts Set (Credential 'Staking)
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetGenesisConfig BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetGenesisConfig
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetGenesisConfig BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
DebugNewEpochState BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
DebugNewEpochState
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
DebugNewEpochState BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
DebugChainDepState BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
DebugChainDepState
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
DebugChainDepState BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetRewardProvenance BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetRewardProvenance
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetRewardProvenance BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetUTxOByTxIn Set TxIn
addrs) (GetUTxOByTxIn Set TxIn
addrs')
| Set TxIn
addrs Set TxIn -> Set TxIn -> Bool
forall a. Eq a => a -> a -> Bool
== Set TxIn
addrs'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetUTxOByTxIn Set TxIn
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetStakePools BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetStakePools
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetStakePools BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetStakePoolParams Set (KeyHash 'StakePool)
poolids) (GetStakePoolParams Set (KeyHash 'StakePool)
poolids')
| Set (KeyHash 'StakePool)
poolids Set (KeyHash 'StakePool) -> Set (KeyHash 'StakePool) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (KeyHash 'StakePool)
poolids'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetStakePoolParams Set (KeyHash 'StakePool)
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetRewardInfoPools BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetRewardInfoPools
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetRewardInfoPools BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetPoolState Maybe (Set (KeyHash 'StakePool))
poolids) (GetPoolState Maybe (Set (KeyHash 'StakePool))
poolids')
| Maybe (Set (KeyHash 'StakePool))
poolids Maybe (Set (KeyHash 'StakePool))
-> Maybe (Set (KeyHash 'StakePool)) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (Set (KeyHash 'StakePool))
poolids'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetPoolState Maybe (Set (KeyHash 'StakePool))
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetStakeSnapshots Maybe (Set (KeyHash 'StakePool))
poolid) (GetStakeSnapshots Maybe (Set (KeyHash 'StakePool))
poolid')
| Maybe (Set (KeyHash 'StakePool))
poolid Maybe (Set (KeyHash 'StakePool))
-> Maybe (Set (KeyHash 'StakePool)) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (Set (KeyHash 'StakePool))
poolid'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetStakeSnapshots Maybe (Set (KeyHash 'StakePool))
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetPoolDistr Maybe (Set (KeyHash 'StakePool))
poolids) (GetPoolDistr Maybe (Set (KeyHash 'StakePool))
poolids')
| Maybe (Set (KeyHash 'StakePool))
poolids Maybe (Set (KeyHash 'StakePool))
-> Maybe (Set (KeyHash 'StakePool)) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (Set (KeyHash 'StakePool))
poolids'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetPoolDistr Maybe (Set (KeyHash 'StakePool))
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetStakeDelegDeposits Set (Credential 'Staking)
stakeCreds) (GetStakeDelegDeposits Set (Credential 'Staking)
stakeCreds')
| Set (Credential 'Staking)
stakeCreds Set (Credential 'Staking) -> Set (Credential 'Staking) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (Credential 'Staking)
stakeCreds'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetStakeDelegDeposits Set (Credential 'Staking)
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetConstitution BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetConstitution = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetConstitution BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetGovState BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetGovState = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetGovState BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex GetDRepState{} GetDRepState{} = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex GetDRepState{} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex GetDRepStakeDistr{} GetDRepStakeDistr{} = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex GetDRepStakeDistr{} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex GetCommitteeMembersState{} GetCommitteeMembersState{} = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex GetCommitteeMembersState{} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetFilteredVoteDelegatees Set (Credential 'Staking)
stakeCreds) (GetFilteredVoteDelegatees Set (Credential 'Staking)
stakeCreds')
| Set (Credential 'Staking)
stakeCreds Set (Credential 'Staking) -> Set (Credential 'Staking) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (Credential 'Staking)
stakeCreds'
= (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
| Bool
otherwise
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex GetFilteredVoteDelegatees {} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex GetAccountState {} GetAccountState {} = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex GetAccountState {} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex GetSPOStakeDistr{} GetSPOStakeDistr{} = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex GetSPOStakeDistr{} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex GetProposals{} GetProposals{} = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex GetProposals{} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex GetRatifyState{} GetRatifyState{} = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex GetRatifyState{} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex GetFuturePParams{} GetFuturePParams{} = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex GetFuturePParams{} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetBigLedgerPeerSnapshot BlockQuery (ShelleyBlock proto era) b
R:BlockQueryShelleyBlock proto era b
GetBigLedgerPeerSnapshot = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex BlockQuery (ShelleyBlock proto era) a
R:BlockQueryShelleyBlock proto era a
GetBigLedgerPeerSnapshot BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex QueryStakePoolDefaultVote{} QueryStakePoolDefaultVote{} = (a :~: b) -> Maybe (a :~: b)
forall a. a -> Maybe a
Just a :~: a
a :~: b
forall {k} (a :: k). a :~: a
Refl
sameDepIndex QueryStakePoolDefaultVote{} BlockQuery (ShelleyBlock proto era) b
_ = Maybe (a :~: b)
forall a. Maybe a
Nothing
deriving instance Eq (BlockQuery (ShelleyBlock proto era) result)
deriving instance Show (BlockQuery (ShelleyBlock proto era) result)
instance ShelleyCompatible proto era => ShowQuery (BlockQuery (ShelleyBlock proto era)) where
showResult :: forall result.
BlockQuery (ShelleyBlock proto era) result -> result -> String
showResult = \case
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetLedgerTip -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetEpochNo -> result -> String
forall a. Show a => a -> String
show
GetNonMyopicMemberRewards {} -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetCurrentPParams -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetProposedPParamsUpdates -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakeDistribution -> result -> String
forall a. Show a => a -> String
show
GetUTxOByAddress {} -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetUTxOWhole -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugEpochState -> result -> String
forall a. Show a => a -> String
show
GetCBOR {} -> result -> String
forall a. Show a => a -> String
show
GetFilteredDelegationsAndRewardAccounts {} -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGenesisConfig -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugNewEpochState -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugChainDepState -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardProvenance -> result -> String
forall a. Show a => a -> String
show
GetUTxOByTxIn {} -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakePools -> result -> String
forall a. Show a => a -> String
show
GetStakePoolParams {} -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardInfoPools -> result -> String
forall a. Show a => a -> String
show
GetPoolState {} -> result -> String
forall a. Show a => a -> String
show
GetStakeSnapshots {} -> result -> String
forall a. Show a => a -> String
show
GetPoolDistr {} -> result -> String
forall a. Show a => a -> String
show
GetStakeDelegDeposits {} -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetConstitution -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGovState -> result -> String
forall a. Show a => a -> String
show
GetDRepState {} -> result -> String
forall a. Show a => a -> String
show
GetDRepStakeDistr {} -> result -> String
forall a. Show a => a -> String
show
GetCommitteeMembersState {} -> result -> String
forall a. Show a => a -> String
show
GetFilteredVoteDelegatees {} -> result -> String
forall a. Show a => a -> String
show
GetAccountState {} -> result -> String
forall a. Show a => a -> String
show
GetSPOStakeDistr {} -> result -> String
forall a. Show a => a -> String
show
GetProposals {} -> result -> String
forall a. Show a => a -> String
show
GetRatifyState {} -> result -> String
forall a. Show a => a -> String
show
GetFuturePParams {} -> result -> String
forall a. Show a => a -> String
show
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetBigLedgerPeerSnapshot -> result -> String
forall a. Show a => a -> String
show
QueryStakePoolDefaultVote {} -> result -> String
forall a. Show a => a -> String
show
getEpochState :: SL.NewEpochState era -> SL.EpochState era
getEpochState :: forall era. NewEpochState era -> EpochState era
getEpochState = NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
SL.nesEs
getDState :: SL.EraCertState era => SL.NewEpochState era -> SL.DState era
getDState :: forall era. EraCertState era => NewEpochState era -> DState era
getDState = Getting (DState era) (CertState era) (DState era)
-> CertState era -> DState era
forall a s. Getting a s a -> s -> a
view Getting (DState era) (CertState era) (DState era)
forall era. EraCertState era => Lens' (CertState era) (DState era)
Lens' (CertState era) (DState era)
SL.certDStateL (CertState era -> DState era)
-> (NewEpochState era -> CertState era)
-> NewEpochState era
-> DState era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState era -> CertState era
forall era. LedgerState era -> CertState era
SL.lsCertState (LedgerState era -> CertState era)
-> (NewEpochState era -> LedgerState era)
-> NewEpochState era
-> CertState era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EpochState era -> LedgerState era
forall era. EpochState era -> LedgerState era
SL.esLState (EpochState era -> LedgerState era)
-> (NewEpochState era -> EpochState era)
-> NewEpochState era
-> LedgerState era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
SL.nesEs
getFilteredDelegationsAndRewardAccounts ::
SL.EraCertState era
=> SL.NewEpochState era
-> Set (SL.Credential 'SL.Staking)
-> (Delegations, Map (SL.Credential 'Staking) Coin)
getFilteredDelegationsAndRewardAccounts :: forall era.
EraCertState era =>
NewEpochState era
-> Set (Credential 'Staking)
-> (Delegations, Map (Credential 'Staking) Coin)
getFilteredDelegationsAndRewardAccounts NewEpochState era
ss Set (Credential 'Staking)
creds =
(Delegations
filteredDelegations, Map (Credential 'Staking) Coin
filteredRwdAcnts)
where
UMap Map (Credential 'Staking) UMElem
umElems Map Ptr (Credential 'Staking)
_ = DState era -> UMap
forall era. DState era -> UMap
SL.dsUnified (DState era -> UMap) -> DState era -> UMap
forall a b. (a -> b) -> a -> b
$ NewEpochState era -> DState era
forall era. EraCertState era => NewEpochState era -> DState era
getDState NewEpochState era
ss
umElemsRestricted :: Map (Credential 'Staking) UMElem
umElemsRestricted = Map (Credential 'Staking) UMElem
-> Set (Credential 'Staking) -> Map (Credential 'Staking) UMElem
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys Map (Credential 'Staking) UMElem
umElems Set (Credential 'Staking)
creds
filteredDelegations :: Delegations
filteredDelegations = (UMElem -> Maybe (KeyHash 'StakePool))
-> Map (Credential 'Staking) UMElem -> Delegations
forall a b k. (a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybe UMElem -> Maybe (KeyHash 'StakePool)
umElemSPool Map (Credential 'Staking) UMElem
umElemsRestricted
filteredRwdAcnts :: Map (Credential 'Staking) Coin
filteredRwdAcnts =
(UMElem -> Maybe Coin)
-> Map (Credential 'Staking) UMElem
-> Map (Credential 'Staking) Coin
forall a b k. (a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybe (\UMElem
e -> CompactForm Coin -> Coin
forall a. Compactible a => CompactForm a -> a
fromCompact (CompactForm Coin -> Coin)
-> (RDPair -> CompactForm Coin) -> RDPair -> Coin
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RDPair -> CompactForm Coin
rdReward (RDPair -> Coin) -> Maybe RDPair -> Maybe Coin
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UMElem -> Maybe RDPair
umElemRDPair UMElem
e) Map (Credential 'Staking) UMElem
umElemsRestricted
getFilteredVoteDelegatees ::
SL.EraCertState era
=> SL.NewEpochState era
-> Set (SL.Credential 'SL.Staking)
-> VoteDelegatees
getFilteredVoteDelegatees :: forall era.
EraCertState era =>
NewEpochState era
-> Set (Credential 'Staking) -> Map (Credential 'Staking) DRep
getFilteredVoteDelegatees NewEpochState era
ss Set (Credential 'Staking)
creds = (UMElem -> Maybe DRep)
-> Map (Credential 'Staking) UMElem
-> Map (Credential 'Staking) DRep
forall a b k. (a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybe UMElem -> Maybe DRep
umElemDRep Map (Credential 'Staking) UMElem
umElemsRestricted
where
UMap Map (Credential 'Staking) UMElem
umElems Map Ptr (Credential 'Staking)
_ = DState era -> UMap
forall era. DState era -> UMap
SL.dsUnified (DState era -> UMap) -> DState era -> UMap
forall a b. (a -> b) -> a -> b
$ NewEpochState era -> DState era
forall era. EraCertState era => NewEpochState era -> DState era
getDState NewEpochState era
ss
umElemsRestricted :: Map (Credential 'Staking) UMElem
umElemsRestricted = Map (Credential 'Staking) UMElem
-> Set (Credential 'Staking) -> Map (Credential 'Staking) UMElem
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys Map (Credential 'Staking) UMElem
umElems Set (Credential 'Staking)
creds
encodeShelleyQuery ::
forall era proto result. ShelleyBasedEra era
=> BlockQuery (ShelleyBlock proto era) result -> Encoding
encodeShelleyQuery :: forall era proto result.
ShelleyBasedEra era =>
BlockQuery (ShelleyBlock proto era) result -> Encoding
encodeShelleyQuery BlockQuery (ShelleyBlock proto era) result
query = case BlockQuery (ShelleyBlock proto era) result
query of
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetLedgerTip ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
0
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetEpochNo ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
1
GetNonMyopicMemberRewards Set (Either Coin (Credential 'Staking))
creds ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Set (Either Coin (Credential 'Staking)) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Either Coin (Credential 'Staking))
creds
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetCurrentPParams ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
3
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetProposedPParamsUpdates ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
4
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakeDistribution ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
5
GetUTxOByAddress Set Addr
addrs ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
6 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era Set Addr
addrs
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetUTxOWhole ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
7
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugEpochState ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
8
GetCBOR BlockQuery (ShelleyBlock proto era) result
query' ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
9 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> BlockQuery (ShelleyBlock proto era) result -> Encoding
forall era proto result.
ShelleyBasedEra era =>
BlockQuery (ShelleyBlock proto era) result -> Encoding
encodeShelleyQuery BlockQuery (ShelleyBlock proto era) result
query'
GetFilteredDelegationsAndRewardAccounts Set (Credential 'Staking)
creds ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
10 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era Set (Credential 'Staking)
creds
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGenesisConfig ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
11
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugNewEpochState ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
12
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugChainDepState ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
13
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardProvenance ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
14
GetUTxOByTxIn Set TxIn
txins ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
15 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era Set TxIn
txins
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakePools ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
16
GetStakePoolParams Set (KeyHash 'StakePool)
poolids ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
17 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Set (KeyHash 'StakePool) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (KeyHash 'StakePool)
poolids
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardInfoPools ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
18
GetPoolState Maybe (Set (KeyHash 'StakePool))
poolids ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
19 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Maybe (Set (KeyHash 'StakePool)) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Maybe (Set (KeyHash 'StakePool))
poolids
GetStakeSnapshots Maybe (Set (KeyHash 'StakePool))
poolId ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
20 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Maybe (Set (KeyHash 'StakePool)) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Maybe (Set (KeyHash 'StakePool))
poolId
GetPoolDistr Maybe (Set (KeyHash 'StakePool))
poolids ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
21 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Maybe (Set (KeyHash 'StakePool)) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Maybe (Set (KeyHash 'StakePool))
poolids
GetStakeDelegDeposits Set (Credential 'Staking)
stakeCreds ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
22 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Set (Credential 'Staking) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Credential 'Staking)
stakeCreds
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetConstitution ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
23
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGovState ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
24
GetDRepState Set (Credential 'DRepRole)
drepCreds ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
25 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Set (Credential 'DRepRole) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Credential 'DRepRole)
drepCreds
GetDRepStakeDistr Set DRep
dreps ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
26 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era Set DRep
dreps
GetCommitteeMembersState Set (Credential 'ColdCommitteeRole)
coldCreds Set (Credential 'HotCommitteeRole)
hotCreds Set MemberStatus
statuses ->
Word -> Encoding
CBOR.encodeListLen Word
4 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
27 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Set (Credential 'ColdCommitteeRole) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Credential 'ColdCommitteeRole)
coldCreds Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Set (Credential 'HotCommitteeRole) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Credential 'HotCommitteeRole)
hotCreds Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era Set MemberStatus
statuses
GetFilteredVoteDelegatees Set (Credential 'Staking)
stakeCreds ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
28 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era Set (Credential 'Staking)
stakeCreds
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetAccountState ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
29
GetSPOStakeDistr Set (KeyHash 'StakePool)
keys ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
30 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era Set (KeyHash 'StakePool)
keys
GetProposals Set GovActionId
gids ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
31 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era Set GovActionId
gids
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRatifyState ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
32
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetFuturePParams ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
33
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetBigLedgerPeerSnapshot ->
Word -> Encoding
CBOR.encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
34
QueryStakePoolDefaultVote KeyHash 'StakePool
stakePoolKey ->
Word -> Encoding
CBOR.encodeListLen Word
2 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
CBOR.encodeWord8 Word8
35 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era KeyHash 'StakePool
stakePoolKey
decodeShelleyQuery ::
forall era proto. ShelleyBasedEra era
=> forall s. Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
decodeShelleyQuery :: forall era proto s.
ShelleyBasedEra era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
decodeShelleyQuery = do
Int
len <- Decoder s Int
forall s. Decoder s Int
CBOR.decodeListLen
Word8
tag <- Decoder s Word8
forall s. Decoder s Word8
CBOR.decodeWord8
let failmsg :: forall s ans. String -> Decoder s ans
failmsg :: forall s ans. String -> Decoder s ans
failmsg String
msg = String -> Decoder s ans
forall a. String -> Decoder s a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Decoder s ans) -> String -> Decoder s ans
forall a b. (a -> b) -> a -> b
$
String
"decodeShelleyQuery: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
msg String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" (len, tag) = (" String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
Int -> String
forall a. Show a => a -> String
show Int
len String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
tag String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
requireCG ::
forall s ans.
(CG.ConwayEraGov era => Decoder s ans)
-> Decoder s ans
requireCG :: forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ConwayEraGov era => Decoder s ans
k = case Proxy era -> Maybe (ConwayEraGovDict era)
forall era (proxy :: * -> *).
ShelleyBasedEra era =>
proxy era -> Maybe (ConwayEraGovDict era)
forall (proxy :: * -> *). proxy era -> Maybe (ConwayEraGovDict era)
SE.getConwayEraGovDict (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @era) of
Just ConwayEraGovDict era
SE.ConwayEraGovDict -> Decoder s ans
ConwayEraGov era => Decoder s ans
k
Maybe (ConwayEraGovDict era)
Nothing -> String -> Decoder s ans
forall s ans. String -> Decoder s ans
failmsg String
"that query is not supported before Conway,"
case (Int
len, Word8
tag) of
(Int
1, Word8
0) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(ShelleyBlock proto era) (Point (ShelleyBlock proto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery
(ShelleyBlock proto era) (Point (ShelleyBlock proto era))
forall proto era.
BlockQuery
(ShelleyBlock proto era) (Point (ShelleyBlock proto era))
GetLedgerTip
(Int
1, Word8
1) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) EpochNo
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) EpochNo
forall proto era. BlockQuery (ShelleyBlock proto era) EpochNo
GetEpochNo
(Int
2, Word8
2) -> BlockQuery (ShelleyBlock proto era) NonMyopicMemberRewards
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) NonMyopicMemberRewards
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Either Coin (Credential 'Staking))
-> BlockQuery (ShelleyBlock proto era) NonMyopicMemberRewards)
-> Set (Either Coin (Credential 'Staking))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Either Coin (Credential 'Staking))
-> BlockQuery (ShelleyBlock proto era) NonMyopicMemberRewards
forall proto era.
Set (Either Coin (Credential 'Staking))
-> BlockQuery (ShelleyBlock proto era) NonMyopicMemberRewards
GetNonMyopicMemberRewards (Set (Either Coin (Credential 'Staking))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Either Coin (Credential 'Staking)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Set (Either Coin (Credential 'Staking)))
forall s. Decoder s (Set (Either Coin (Credential 'Staking)))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
1, Word8
3) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (PParams era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (PParams era)
forall proto era. BlockQuery (ShelleyBlock proto era) (PParams era)
GetCurrentPParams
(Int
1, Word8
4) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (ProposedPPUpdates era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (ProposedPPUpdates era)
forall proto era.
BlockQuery (ShelleyBlock proto era) (ProposedPPUpdates era)
GetProposedPParamsUpdates
(Int
1, Word8
5) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (PoolDistr (ProtoCrypto proto))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (PoolDistr (ProtoCrypto proto))
forall proto era.
BlockQuery (ShelleyBlock proto era) (PoolDistr (ProtoCrypto proto))
GetStakeDistribution
(Int
2, Word8
6) -> BlockQuery (ShelleyBlock proto era) (UTxO era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) (UTxO era)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set Addr -> BlockQuery (ShelleyBlock proto era) (UTxO era))
-> Set Addr
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set Addr -> BlockQuery (ShelleyBlock proto era) (UTxO era)
forall proto era.
Set Addr -> BlockQuery (ShelleyBlock proto era) (UTxO era)
GetUTxOByAddress (Set Addr -> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set Addr)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
(Int
1, Word8
7) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (UTxO era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (UTxO era)
forall proto era. BlockQuery (ShelleyBlock proto era) (UTxO era)
GetUTxOWhole
(Int
1, Word8
8) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (EpochState era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (EpochState era)
forall proto era.
BlockQuery (ShelleyBlock proto era) (EpochState era)
DebugEpochState
(Int
2, Word8
9) -> (\(SomeSecond BlockQuery (ShelleyBlock proto era) b
q) -> BlockQuery (ShelleyBlock proto era) (Serialised b)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) b
-> BlockQuery (ShelleyBlock proto era) (Serialised b)
forall proto era result.
BlockQuery (ShelleyBlock proto era) result
-> BlockQuery (ShelleyBlock proto era) (Serialised result)
GetCBOR BlockQuery (ShelleyBlock proto era) b
q)) (SomeSecond BlockQuery (ShelleyBlock proto era)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s.
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall era proto s.
ShelleyBasedEra era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
decodeShelleyQuery
(Int
2, Word8
10) -> BlockQuery
(ShelleyBlock proto era)
(Delegations, Map (Credential 'Staking) Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery
(ShelleyBlock proto era)
(Delegations, Map (Credential 'Staking) Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Credential 'Staking)
-> BlockQuery
(ShelleyBlock proto era)
(Delegations, Map (Credential 'Staking) Coin))
-> Set (Credential 'Staking)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Credential 'Staking)
-> BlockQuery
(ShelleyBlock proto era)
(Delegations, Map (Credential 'Staking) Coin)
forall proto era.
Set (Credential 'Staking)
-> BlockQuery
(ShelleyBlock proto era)
(Delegations, Map (Credential 'Staking) Coin)
GetFilteredDelegationsAndRewardAccounts (Set (Credential 'Staking)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Credential 'Staking))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
(Int
1, Word8
11) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) CompactGenesis
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) CompactGenesis
forall proto era.
BlockQuery (ShelleyBlock proto era) CompactGenesis
GetGenesisConfig
(Int
1, Word8
12) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (NewEpochState era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (NewEpochState era)
forall proto era.
BlockQuery (ShelleyBlock proto era) (NewEpochState era)
DebugNewEpochState
(Int
1, Word8
13) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (ChainDepState proto)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (ChainDepState proto)
forall proto era.
BlockQuery (ShelleyBlock proto era) (ChainDepState proto)
DebugChainDepState
(Int
1, Word8
14) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) RewardProvenance
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) RewardProvenance
forall proto era.
BlockQuery (ShelleyBlock proto era) RewardProvenance
GetRewardProvenance
(Int
2, Word8
15) -> BlockQuery (ShelleyBlock proto era) (UTxO era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) (UTxO era)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set TxIn -> BlockQuery (ShelleyBlock proto era) (UTxO era))
-> Set TxIn
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set TxIn -> BlockQuery (ShelleyBlock proto era) (UTxO era)
forall proto era.
Set TxIn -> BlockQuery (ShelleyBlock proto era) (UTxO era)
GetUTxOByTxIn (Set TxIn -> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set TxIn)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
(Int
1, Word8
16) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (Set (KeyHash 'StakePool))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (Set (KeyHash 'StakePool))
forall proto era.
BlockQuery (ShelleyBlock proto era) (Set (KeyHash 'StakePool))
GetStakePools
(Int
2, Word8
17) -> BlockQuery
(ShelleyBlock proto era) (Map (KeyHash 'StakePool) PoolParams)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery
(ShelleyBlock proto era) (Map (KeyHash 'StakePool) PoolParams)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (KeyHash 'StakePool)
-> BlockQuery
(ShelleyBlock proto era) (Map (KeyHash 'StakePool) PoolParams))
-> Set (KeyHash 'StakePool)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (KeyHash 'StakePool)
-> BlockQuery
(ShelleyBlock proto era) (Map (KeyHash 'StakePool) PoolParams)
forall proto era.
Set (KeyHash 'StakePool)
-> BlockQuery
(ShelleyBlock proto era) (Map (KeyHash 'StakePool) PoolParams)
GetStakePoolParams (Set (KeyHash 'StakePool)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (KeyHash 'StakePool))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Set (KeyHash 'StakePool))
forall s. Decoder s (Set (KeyHash 'StakePool))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
1, Word8
18) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(ShelleyBlock proto era)
(RewardParams, Map (KeyHash 'StakePool) RewardInfoPool)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery
(ShelleyBlock proto era)
(RewardParams, Map (KeyHash 'StakePool) RewardInfoPool)
forall proto era.
BlockQuery
(ShelleyBlock proto era)
(RewardParams, Map (KeyHash 'StakePool) RewardInfoPool)
GetRewardInfoPools
(Int
2, Word8
19) -> BlockQuery (ShelleyBlock proto era) (PState era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) (PState era)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Maybe (Set (KeyHash 'StakePool))
-> BlockQuery (ShelleyBlock proto era) (PState era))
-> Maybe (Set (KeyHash 'StakePool))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Set (KeyHash 'StakePool))
-> BlockQuery (ShelleyBlock proto era) (PState era)
forall proto era.
Maybe (Set (KeyHash 'StakePool))
-> BlockQuery (ShelleyBlock proto era) (PState era)
GetPoolState (Maybe (Set (KeyHash 'StakePool))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Maybe (Set (KeyHash 'StakePool)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Maybe (Set (KeyHash 'StakePool)))
forall s. Decoder s (Maybe (Set (KeyHash 'StakePool)))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
2, Word8
20) -> BlockQuery (ShelleyBlock proto era) StakeSnapshots
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) StakeSnapshots
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Maybe (Set (KeyHash 'StakePool))
-> BlockQuery (ShelleyBlock proto era) StakeSnapshots)
-> Maybe (Set (KeyHash 'StakePool))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Set (KeyHash 'StakePool))
-> BlockQuery (ShelleyBlock proto era) StakeSnapshots
forall proto era.
Maybe (Set (KeyHash 'StakePool))
-> BlockQuery (ShelleyBlock proto era) StakeSnapshots
GetStakeSnapshots (Maybe (Set (KeyHash 'StakePool))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Maybe (Set (KeyHash 'StakePool)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Maybe (Set (KeyHash 'StakePool)))
forall s. Decoder s (Maybe (Set (KeyHash 'StakePool)))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
2, Word8
21) -> BlockQuery (ShelleyBlock proto era) (PoolDistr (ProtoCrypto proto))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery
(ShelleyBlock proto era) (PoolDistr (ProtoCrypto proto))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Maybe (Set (KeyHash 'StakePool))
-> BlockQuery
(ShelleyBlock proto era) (PoolDistr (ProtoCrypto proto)))
-> Maybe (Set (KeyHash 'StakePool))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Set (KeyHash 'StakePool))
-> BlockQuery
(ShelleyBlock proto era) (PoolDistr (ProtoCrypto proto))
forall proto era.
Maybe (Set (KeyHash 'StakePool))
-> BlockQuery
(ShelleyBlock proto era) (PoolDistr (ProtoCrypto proto))
GetPoolDistr (Maybe (Set (KeyHash 'StakePool))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Maybe (Set (KeyHash 'StakePool)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Maybe (Set (KeyHash 'StakePool)))
forall s. Decoder s (Maybe (Set (KeyHash 'StakePool)))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
2, Word8
22) -> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Credential 'Staking)
-> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) Coin))
-> Set (Credential 'Staking)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Credential 'Staking)
-> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) Coin)
forall proto era.
Set (Credential 'Staking)
-> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) Coin)
GetStakeDelegDeposits (Set (Credential 'Staking)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Credential 'Staking))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Set (Credential 'Staking))
forall s. Decoder s (Set (Credential 'Staking))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
1, Word8
23) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (Constitution era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (Constitution era)
forall era proto.
ConwayEraGov era =>
BlockQuery (ShelleyBlock proto era) (Constitution era)
GetConstitution
(Int
1, Word8
24) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (GovState era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (GovState era)
forall proto era.
BlockQuery (ShelleyBlock proto era) (GovState era)
GetGovState
(Int
2, Word8
25) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(ShelleyBlock proto era) (Map (Credential 'DRepRole) DRepState)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery
(ShelleyBlock proto era) (Map (Credential 'DRepRole) DRepState)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Credential 'DRepRole)
-> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'DRepRole) DRepState))
-> Set (Credential 'DRepRole)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Credential 'DRepRole)
-> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'DRepRole) DRepState)
forall era proto.
ConwayEraGov era =>
Set (Credential 'DRepRole)
-> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'DRepRole) DRepState)
GetDRepState (Set (Credential 'DRepRole)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Credential 'DRepRole))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Set (Credential 'DRepRole))
forall s. Decoder s (Set (Credential 'DRepRole))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
2, Word8
26) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (Map DRep Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) (Map DRep Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set DRep
-> BlockQuery (ShelleyBlock proto era) (Map DRep Coin))
-> Set DRep
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set DRep -> BlockQuery (ShelleyBlock proto era) (Map DRep Coin)
forall era proto.
ConwayEraGov era =>
Set DRep -> BlockQuery (ShelleyBlock proto era) (Map DRep Coin)
GetDRepStakeDistr (Set DRep -> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set DRep)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
(Int
4, Word8
27) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ do
Set (Credential 'ColdCommitteeRole)
coldCreds <- Decoder s (Set (Credential 'ColdCommitteeRole))
forall s. Decoder s (Set (Credential 'ColdCommitteeRole))
forall a s. FromCBOR a => Decoder s a
fromCBOR
Set (Credential 'HotCommitteeRole)
hotCreds <- Decoder s (Set (Credential 'HotCommitteeRole))
forall s. Decoder s (Set (Credential 'HotCommitteeRole))
forall a s. FromCBOR a => Decoder s a
fromCBOR
Set MemberStatus
statuses <- forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) CommitteeMembersState
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) CommitteeMembersState
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> BlockQuery (ShelleyBlock proto era) CommitteeMembersState
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall a b. (a -> b) -> a -> b
$ Set (Credential 'ColdCommitteeRole)
-> Set (Credential 'HotCommitteeRole)
-> Set MemberStatus
-> BlockQuery (ShelleyBlock proto era) CommitteeMembersState
forall era proto.
ConwayEraGov era =>
Set (Credential 'ColdCommitteeRole)
-> Set (Credential 'HotCommitteeRole)
-> Set MemberStatus
-> BlockQuery (ShelleyBlock proto era) CommitteeMembersState
GetCommitteeMembersState Set (Credential 'ColdCommitteeRole)
coldCreds Set (Credential 'HotCommitteeRole)
hotCreds Set MemberStatus
statuses
(Int
2, Word8
28) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ do
BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) DRep)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) DRep)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Credential 'Staking)
-> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) DRep))
-> Set (Credential 'Staking)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Credential 'Staking)
-> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) DRep)
forall era proto.
ConwayEraGov era =>
Set (Credential 'Staking)
-> BlockQuery
(ShelleyBlock proto era) (Map (Credential 'Staking) DRep)
GetFilteredVoteDelegatees (Set (Credential 'Staking)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Credential 'Staking))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
(Int
1, Word8
29) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) AccountState
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) AccountState
forall proto era. BlockQuery (ShelleyBlock proto era) AccountState
GetAccountState
(Int
2, Word8
30) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (Map (KeyHash 'StakePool) Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery
(ShelleyBlock proto era) (Map (KeyHash 'StakePool) Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (KeyHash 'StakePool)
-> BlockQuery
(ShelleyBlock proto era) (Map (KeyHash 'StakePool) Coin))
-> Set (KeyHash 'StakePool)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (KeyHash 'StakePool)
-> BlockQuery
(ShelleyBlock proto era) (Map (KeyHash 'StakePool) Coin)
forall era proto.
ConwayEraGov era =>
Set (KeyHash 'StakePool)
-> BlockQuery
(ShelleyBlock proto era) (Map (KeyHash 'StakePool) Coin)
GetSPOStakeDistr (Set (KeyHash 'StakePool)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (KeyHash 'StakePool))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
(Int
2, Word8
31) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (Seq (GovActionState era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) (Seq (GovActionState era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set GovActionId
-> BlockQuery (ShelleyBlock proto era) (Seq (GovActionState era)))
-> Set GovActionId
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set GovActionId
-> BlockQuery (ShelleyBlock proto era) (Seq (GovActionState era))
forall era proto.
ConwayEraGov era =>
Set GovActionId
-> BlockQuery (ShelleyBlock proto era) (Seq (GovActionState era))
GetProposals (Set GovActionId -> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set GovActionId)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
(Int
1, Word8
32) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (RatifyState era)
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (RatifyState era)
forall era proto.
ConwayEraGov era =>
BlockQuery (ShelleyBlock proto era) (RatifyState era)
GetRatifyState
(Int
1, Word8
33) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) (Maybe (PParams era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) (Maybe (PParams era))
forall proto era.
BlockQuery (ShelleyBlock proto era) (Maybe (PParams era))
GetFuturePParams
(Int
1, Word8
34) -> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a. a -> Decoder s a
forall (m :: * -> *) a. Monad m => a -> m a
return (SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) LedgerPeerSnapshot
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery (ShelleyBlock proto era) LedgerPeerSnapshot
forall proto era.
BlockQuery (ShelleyBlock proto era) LedgerPeerSnapshot
GetBigLedgerPeerSnapshot
(Int
2, Word8
35) -> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. (ConwayEraGov era => Decoder s ans) -> Decoder s ans
requireCG ((ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> (ConwayEraGov era =>
Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall a b. (a -> b) -> a -> b
$ BlockQuery (ShelleyBlock proto era) DefaultVote
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (BlockQuery (ShelleyBlock proto era) DefaultVote
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (KeyHash 'StakePool
-> BlockQuery (ShelleyBlock proto era) DefaultVote)
-> KeyHash 'StakePool
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyHash 'StakePool
-> BlockQuery (ShelleyBlock proto era) DefaultVote
forall era proto.
ConwayEraGov era =>
KeyHash 'StakePool
-> BlockQuery (ShelleyBlock proto era) DefaultVote
QueryStakePoolDefaultVote (KeyHash 'StakePool
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (KeyHash 'StakePool)
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
(Int, Word8)
_ -> String
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall s ans. String -> Decoder s ans
failmsg String
"invalid"
encodeShelleyResult ::
forall proto era result. ShelleyCompatible proto era
=> ShelleyNodeToClientVersion
-> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding
encodeShelleyResult :: forall proto era result.
ShelleyCompatible proto era =>
ShelleyNodeToClientVersion
-> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding
encodeShelleyResult ShelleyNodeToClientVersion
_v BlockQuery (ShelleyBlock proto era) result
query = case BlockQuery (ShelleyBlock proto era) result
query of
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetLedgerTip -> (HeaderHash (ShelleyBlock proto era) -> Encoding)
-> Point (ShelleyBlock proto era) -> Encoding
forall {k} (block :: k).
(HeaderHash block -> Encoding) -> Point block -> Encoding
encodePoint HeaderHash (ShelleyBlock proto era) -> Encoding
ShelleyHash -> Encoding
forall a. Serialise a => a -> Encoding
encode
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetEpochNo -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
GetNonMyopicMemberRewards {} -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetCurrentPParams -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetProposedPParamsUpdates -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakeDistribution -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetUTxOByAddress {} -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetUTxOWhole -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugEpochState -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
GetCBOR {} -> result -> Encoding
forall a. Serialise a => a -> Encoding
encode
GetFilteredDelegationsAndRewardAccounts {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGenesisConfig -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugNewEpochState -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugChainDepState -> result -> Encoding
forall a. Serialise a => a -> Encoding
encode
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardProvenance -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetUTxOByTxIn {} -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakePools -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
GetStakePoolParams {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardInfoPools -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetPoolState {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetStakeSnapshots {} -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
GetPoolDistr {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetStakeDelegDeposits {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetConstitution -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGovState -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
GetDRepState {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetDRepStakeDistr {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetCommitteeMembersState {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetFilteredVoteDelegatees {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetAccountState {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetSPOStakeDistr {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetProposals {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetRatifyState {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
GetFuturePParams {} -> forall era t. (Era era, EncCBOR t) => t -> Encoding
LC.toEraCBOR @era
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetBigLedgerPeerSnapshot -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
QueryStakePoolDefaultVote {} -> result -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
decodeShelleyResult ::
forall proto era result. ShelleyCompatible proto era
=> ShelleyNodeToClientVersion
-> BlockQuery (ShelleyBlock proto era) result
-> forall s. Decoder s result
decodeShelleyResult :: forall proto era result.
ShelleyCompatible proto era =>
ShelleyNodeToClientVersion
-> BlockQuery (ShelleyBlock proto era) result
-> forall s. Decoder s result
decodeShelleyResult ShelleyNodeToClientVersion
_v BlockQuery (ShelleyBlock proto era) result
query = case BlockQuery (ShelleyBlock proto era) result
query of
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetLedgerTip -> (forall s. Decoder s (HeaderHash (ShelleyBlock proto era)))
-> forall s. Decoder s (Point (ShelleyBlock proto era))
forall {k} (block :: k).
(forall s. Decoder s (HeaderHash block))
-> forall s. Decoder s (Point block)
decodePoint Decoder s (HeaderHash (ShelleyBlock proto era))
Decoder s ShelleyHash
forall s. Decoder s (HeaderHash (ShelleyBlock proto era))
forall s. Decoder s ShelleyHash
forall a s. Serialise a => Decoder s a
decode
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetEpochNo -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
GetNonMyopicMemberRewards {} -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetCurrentPParams -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetProposedPParamsUpdates -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakeDistribution -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetUTxOByAddress {} -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetUTxOWhole -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugEpochState -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
GetCBOR {} -> Decoder s result
forall s. Decoder s result
forall a s. Serialise a => Decoder s a
decode
GetFilteredDelegationsAndRewardAccounts {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGenesisConfig -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugNewEpochState -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugChainDepState -> Decoder s result
forall s. Decoder s result
forall a s. Serialise a => Decoder s a
decode
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardProvenance -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetUTxOByTxIn {} -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakePools -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
GetStakePoolParams {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardInfoPools -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetPoolState {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetStakeSnapshots {} -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
GetPoolDistr {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetStakeDelegDeposits {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetConstitution -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGovState -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
GetDRepState {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetDRepStakeDistr {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetCommitteeMembersState {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetFilteredVoteDelegatees {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetAccountState {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetSPOStakeDistr {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetProposals {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetRatifyState {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
GetFuturePParams {} -> forall era t s. (Era era, DecCBOR t) => Decoder s t
LC.fromEraCBOR @era
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetBigLedgerPeerSnapshot -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
QueryStakePoolDefaultVote {} -> Decoder s result
forall s. Decoder s result
forall a s. FromCBOR a => Decoder s a
fromCBOR
data StakeSnapshot = StakeSnapshot
{ StakeSnapshot -> Coin
ssMarkPool :: !SL.Coin
, StakeSnapshot -> Coin
ssSetPool :: !SL.Coin
, StakeSnapshot -> Coin
ssGoPool :: !SL.Coin
} deriving (StakeSnapshot -> StakeSnapshot -> Bool
(StakeSnapshot -> StakeSnapshot -> Bool)
-> (StakeSnapshot -> StakeSnapshot -> Bool) -> Eq StakeSnapshot
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StakeSnapshot -> StakeSnapshot -> Bool
== :: StakeSnapshot -> StakeSnapshot -> Bool
$c/= :: StakeSnapshot -> StakeSnapshot -> Bool
/= :: StakeSnapshot -> StakeSnapshot -> Bool
Eq, Int -> StakeSnapshot -> ShowS
[StakeSnapshot] -> ShowS
StakeSnapshot -> String
(Int -> StakeSnapshot -> ShowS)
-> (StakeSnapshot -> String)
-> ([StakeSnapshot] -> ShowS)
-> Show StakeSnapshot
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StakeSnapshot -> ShowS
showsPrec :: Int -> StakeSnapshot -> ShowS
$cshow :: StakeSnapshot -> String
show :: StakeSnapshot -> String
$cshowList :: [StakeSnapshot] -> ShowS
showList :: [StakeSnapshot] -> ShowS
Show, (forall x. StakeSnapshot -> Rep StakeSnapshot x)
-> (forall x. Rep StakeSnapshot x -> StakeSnapshot)
-> Generic StakeSnapshot
forall x. Rep StakeSnapshot x -> StakeSnapshot
forall x. StakeSnapshot -> Rep StakeSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StakeSnapshot -> Rep StakeSnapshot x
from :: forall x. StakeSnapshot -> Rep StakeSnapshot x
$cto :: forall x. Rep StakeSnapshot x -> StakeSnapshot
to :: forall x. Rep StakeSnapshot x -> StakeSnapshot
Generic)
instance NFData StakeSnapshot
instance
ToCBOR StakeSnapshot
where
toCBOR :: StakeSnapshot -> Encoding
toCBOR
StakeSnapshot
{ Coin
ssMarkPool :: StakeSnapshot -> Coin
ssMarkPool :: Coin
ssMarkPool
, Coin
ssSetPool :: StakeSnapshot -> Coin
ssSetPool :: Coin
ssSetPool
, Coin
ssGoPool :: StakeSnapshot -> Coin
ssGoPool :: Coin
ssGoPool
} = Word -> Encoding
encodeListLen Word
3
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Coin -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Coin
ssMarkPool
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Coin -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Coin
ssSetPool
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Coin -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Coin
ssGoPool
instance
FromCBOR StakeSnapshot
where
fromCBOR :: forall s. Decoder s StakeSnapshot
fromCBOR = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"StakeSnapshot" Int
3
Coin -> Coin -> Coin -> StakeSnapshot
StakeSnapshot
(Coin -> Coin -> Coin -> StakeSnapshot)
-> Decoder s Coin -> Decoder s (Coin -> Coin -> StakeSnapshot)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Coin
forall s. Decoder s Coin
forall a s. FromCBOR a => Decoder s a
fromCBOR
Decoder s (Coin -> Coin -> StakeSnapshot)
-> Decoder s Coin -> Decoder s (Coin -> StakeSnapshot)
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s Coin
forall s. Decoder s Coin
forall a s. FromCBOR a => Decoder s a
fromCBOR
Decoder s (Coin -> StakeSnapshot)
-> Decoder s Coin -> Decoder s StakeSnapshot
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s Coin
forall s. Decoder s Coin
forall a s. FromCBOR a => Decoder s a
fromCBOR
data StakeSnapshots = StakeSnapshots
{ StakeSnapshots -> Map (KeyHash 'StakePool) StakeSnapshot
ssStakeSnapshots :: !(Map (SL.KeyHash 'SL.StakePool) StakeSnapshot)
, StakeSnapshots -> Coin
ssMarkTotal :: !SL.Coin
, StakeSnapshots -> Coin
ssSetTotal :: !SL.Coin
, StakeSnapshots -> Coin
ssGoTotal :: !SL.Coin
} deriving (StakeSnapshots -> StakeSnapshots -> Bool
(StakeSnapshots -> StakeSnapshots -> Bool)
-> (StakeSnapshots -> StakeSnapshots -> Bool) -> Eq StakeSnapshots
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StakeSnapshots -> StakeSnapshots -> Bool
== :: StakeSnapshots -> StakeSnapshots -> Bool
$c/= :: StakeSnapshots -> StakeSnapshots -> Bool
/= :: StakeSnapshots -> StakeSnapshots -> Bool
Eq, Int -> StakeSnapshots -> ShowS
[StakeSnapshots] -> ShowS
StakeSnapshots -> String
(Int -> StakeSnapshots -> ShowS)
-> (StakeSnapshots -> String)
-> ([StakeSnapshots] -> ShowS)
-> Show StakeSnapshots
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StakeSnapshots -> ShowS
showsPrec :: Int -> StakeSnapshots -> ShowS
$cshow :: StakeSnapshots -> String
show :: StakeSnapshots -> String
$cshowList :: [StakeSnapshots] -> ShowS
showList :: [StakeSnapshots] -> ShowS
Show, (forall x. StakeSnapshots -> Rep StakeSnapshots x)
-> (forall x. Rep StakeSnapshots x -> StakeSnapshots)
-> Generic StakeSnapshots
forall x. Rep StakeSnapshots x -> StakeSnapshots
forall x. StakeSnapshots -> Rep StakeSnapshots x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StakeSnapshots -> Rep StakeSnapshots x
from :: forall x. StakeSnapshots -> Rep StakeSnapshots x
$cto :: forall x. Rep StakeSnapshots x -> StakeSnapshots
to :: forall x. Rep StakeSnapshots x -> StakeSnapshots
Generic)
instance NFData StakeSnapshots
instance
ToCBOR StakeSnapshots
where
toCBOR :: StakeSnapshots -> Encoding
toCBOR
StakeSnapshots
{ Map (KeyHash 'StakePool) StakeSnapshot
ssStakeSnapshots :: StakeSnapshots -> Map (KeyHash 'StakePool) StakeSnapshot
ssStakeSnapshots :: Map (KeyHash 'StakePool) StakeSnapshot
ssStakeSnapshots
, Coin
ssMarkTotal :: StakeSnapshots -> Coin
ssMarkTotal :: Coin
ssMarkTotal
, Coin
ssSetTotal :: StakeSnapshots -> Coin
ssSetTotal :: Coin
ssSetTotal
, Coin
ssGoTotal :: StakeSnapshots -> Coin
ssGoTotal :: Coin
ssGoTotal
} = Word -> Encoding
encodeListLen Word
4
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Map (KeyHash 'StakePool) StakeSnapshot -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Map (KeyHash 'StakePool) StakeSnapshot
ssStakeSnapshots
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Coin -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Coin
ssMarkTotal
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Coin -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Coin
ssSetTotal
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Coin -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Coin
ssGoTotal
instance
FromCBOR StakeSnapshots
where
fromCBOR :: forall s. Decoder s StakeSnapshots
fromCBOR = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"StakeSnapshots" Int
4
Map (KeyHash 'StakePool) StakeSnapshot
-> Coin -> Coin -> Coin -> StakeSnapshots
StakeSnapshots
(Map (KeyHash 'StakePool) StakeSnapshot
-> Coin -> Coin -> Coin -> StakeSnapshots)
-> Decoder s (Map (KeyHash 'StakePool) StakeSnapshot)
-> Decoder s (Coin -> Coin -> Coin -> StakeSnapshots)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Map (KeyHash 'StakePool) StakeSnapshot)
forall s. Decoder s (Map (KeyHash 'StakePool) StakeSnapshot)
forall a s. FromCBOR a => Decoder s a
fromCBOR
Decoder s (Coin -> Coin -> Coin -> StakeSnapshots)
-> Decoder s Coin -> Decoder s (Coin -> Coin -> StakeSnapshots)
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s Coin
forall s. Decoder s Coin
forall a s. FromCBOR a => Decoder s a
fromCBOR
Decoder s (Coin -> Coin -> StakeSnapshots)
-> Decoder s Coin -> Decoder s (Coin -> StakeSnapshots)
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s Coin
forall s. Decoder s Coin
forall a s. FromCBOR a => Decoder s a
fromCBOR
Decoder s (Coin -> StakeSnapshots)
-> Decoder s Coin -> Decoder s StakeSnapshots
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s Coin
forall s. Decoder s Coin
forall a s. FromCBOR a => Decoder s a
fromCBOR