{-# 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 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ouroboros.Consensus.Shelley.Ledger.Query (
BlockQuery (..)
, NonMyopicMemberRewards (..)
, StakeSnapshot (..)
, StakeSnapshots (..)
, querySupportedVersion
, 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.Crypto (Crypto)
import qualified Cardano.Ledger.EpochBoundary as SL
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.LedgerState as SL (RewardAccounts,
newEpochStateGovStateL)
import qualified Cardano.Ledger.Shelley.PParams as SL (emptyPPPUpdates)
import qualified Cardano.Ledger.Shelley.RewardProvenance as SL
(RewardProvenance)
import Cardano.Ledger.UMap (UMap (..), rdReward, umElemDRep,
umElemRDPair, umElemSPool)
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.Maybe (fromMaybe)
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 Ouroboros.Consensus.Shelley.Eras (EraCrypto)
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.PParamsLegacyEncoder
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 c = NonMyopicMemberRewards {
forall c.
NonMyopicMemberRewards c
-> Map
(Either Coin (Credential 'Staking c))
(Map (KeyHash 'StakePool c) Coin)
unNonMyopicMemberRewards ::
Map (Either SL.Coin (SL.Credential 'SL.Staking c))
(Map (SL.KeyHash 'SL.StakePool c) SL.Coin)
}
deriving stock (Int -> NonMyopicMemberRewards c -> ShowS
[NonMyopicMemberRewards c] -> ShowS
NonMyopicMemberRewards c -> String
(Int -> NonMyopicMemberRewards c -> ShowS)
-> (NonMyopicMemberRewards c -> String)
-> ([NonMyopicMemberRewards c] -> ShowS)
-> Show (NonMyopicMemberRewards c)
forall c. Int -> NonMyopicMemberRewards c -> ShowS
forall c. [NonMyopicMemberRewards c] -> ShowS
forall c. NonMyopicMemberRewards c -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall c. Int -> NonMyopicMemberRewards c -> ShowS
showsPrec :: Int -> NonMyopicMemberRewards c -> ShowS
$cshow :: forall c. NonMyopicMemberRewards c -> String
show :: NonMyopicMemberRewards c -> String
$cshowList :: forall c. [NonMyopicMemberRewards c] -> ShowS
showList :: [NonMyopicMemberRewards c] -> ShowS
Show)
deriving newtype (NonMyopicMemberRewards c -> NonMyopicMemberRewards c -> Bool
(NonMyopicMemberRewards c -> NonMyopicMemberRewards c -> Bool)
-> (NonMyopicMemberRewards c -> NonMyopicMemberRewards c -> Bool)
-> Eq (NonMyopicMemberRewards c)
forall c.
NonMyopicMemberRewards c -> NonMyopicMemberRewards c -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall c.
NonMyopicMemberRewards c -> NonMyopicMemberRewards c -> Bool
== :: NonMyopicMemberRewards c -> NonMyopicMemberRewards c -> Bool
$c/= :: forall c.
NonMyopicMemberRewards c -> NonMyopicMemberRewards c -> Bool
/= :: NonMyopicMemberRewards c -> NonMyopicMemberRewards c -> Bool
Eq, Typeable (NonMyopicMemberRewards c)
Typeable (NonMyopicMemberRewards c) =>
(NonMyopicMemberRewards c -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (NonMyopicMemberRewards c) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonMyopicMemberRewards c] -> Size)
-> ToCBOR (NonMyopicMemberRewards c)
NonMyopicMemberRewards c -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonMyopicMemberRewards c] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (NonMyopicMemberRewards c) -> 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
forall c. Crypto c => Typeable (NonMyopicMemberRewards c)
forall c. Crypto c => NonMyopicMemberRewards c -> Encoding
forall c.
Crypto c =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonMyopicMemberRewards c] -> Size
forall c.
Crypto c =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (NonMyopicMemberRewards c) -> Size
$ctoCBOR :: forall c. Crypto c => NonMyopicMemberRewards c -> Encoding
toCBOR :: NonMyopicMemberRewards c -> Encoding
$cencodedSizeExpr :: forall c.
Crypto c =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (NonMyopicMemberRewards c) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (NonMyopicMemberRewards c) -> Size
$cencodedListSizeExpr :: forall c.
Crypto c =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonMyopicMemberRewards c] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [NonMyopicMemberRewards c] -> Size
ToCBOR, Typeable (NonMyopicMemberRewards c)
Typeable (NonMyopicMemberRewards c) =>
(forall s. Decoder s (NonMyopicMemberRewards c))
-> (Proxy (NonMyopicMemberRewards c) -> Text)
-> FromCBOR (NonMyopicMemberRewards c)
Proxy (NonMyopicMemberRewards c) -> Text
forall s. Decoder s (NonMyopicMemberRewards c)
forall a.
Typeable a =>
(forall s. Decoder s a) -> (Proxy a -> Text) -> FromCBOR a
forall c. Crypto c => Typeable (NonMyopicMemberRewards c)
forall c. Crypto c => Proxy (NonMyopicMemberRewards c) -> Text
forall c s. Crypto c => Decoder s (NonMyopicMemberRewards c)
$cfromCBOR :: forall c s. Crypto c => Decoder s (NonMyopicMemberRewards c)
fromCBOR :: forall s. Decoder s (NonMyopicMemberRewards c)
$clabel :: forall c. Crypto c => Proxy (NonMyopicMemberRewards c) -> Text
label :: Proxy (NonMyopicMemberRewards c) -> Text
FromCBOR)
type Delegations c =
Map (SL.Credential 'SL.Staking c)
(SL.KeyHash 'SL.StakePool c)
type VoteDelegatees c =
Map (SL.Credential 'SL.Staking c)
(SL.DRep c)
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 (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era) (NonMyopicMemberRewards (EraCrypto era))
GetCurrentPParams
:: BlockQuery (ShelleyBlock proto era) (LC.PParams era)
GetProposedPParamsUpdates
:: BlockQuery (ShelleyBlock proto era) (SL.ProposedPPUpdates era)
GetStakeDistribution
:: BlockQuery (ShelleyBlock proto era) (PoolDistr (EraCrypto era))
GetUTxOByAddress
:: Set (SL.Addr (EraCrypto era))
-> 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 (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era)
(Delegations (EraCrypto era), SL.RewardAccounts (EraCrypto era))
GetGenesisConfig
:: BlockQuery (ShelleyBlock proto era) (CompactGenesis (EraCrypto era))
DebugNewEpochState
:: BlockQuery (ShelleyBlock proto era) (SL.NewEpochState era)
DebugChainDepState
:: BlockQuery (ShelleyBlock proto era) (ChainDepState proto)
GetRewardProvenance
:: BlockQuery (ShelleyBlock proto era) (SL.RewardProvenance (EraCrypto era))
GetUTxOByTxIn
:: Set (SL.TxIn (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (SL.UTxO era)
GetStakePools
:: BlockQuery (ShelleyBlock proto era)
(Set (SL.KeyHash 'SL.StakePool (EraCrypto era)))
GetStakePoolParams
:: Set (SL.KeyHash 'SL.StakePool (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era)
(Map (SL.KeyHash 'SL.StakePool (EraCrypto era))
(SL.PoolParams (EraCrypto era)))
GetRewardInfoPools
:: BlockQuery (ShelleyBlock proto era)
(SL.RewardParams,
Map (SL.KeyHash 'SL.StakePool (EraCrypto era))
(SL.RewardInfoPool))
GetPoolState
:: Maybe (Set (SL.KeyHash 'SL.StakePool (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era)
(SL.PState era)
GetStakeSnapshots
:: Maybe (Set (SL.KeyHash 'SL.StakePool (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era)
(StakeSnapshots (EraCrypto era))
GetPoolDistr
:: Maybe (Set (SL.KeyHash 'SL.StakePool (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era)
(PoolDistr (EraCrypto era))
GetStakeDelegDeposits
:: Set (StakeCredential (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era)
(Map (StakeCredential (EraCrypto era)) 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 (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era)
(Map
(SL.Credential 'DRepRole (EraCrypto era))
(SL.DRepState (EraCrypto era))
)
GetDRepStakeDistr
:: CG.ConwayEraGov era
=> Set (SL.DRep (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (Map (SL.DRep (EraCrypto era)) Coin)
:: CG.ConwayEraGov era
=> Set (SL.Credential 'ColdCommitteeRole (EraCrypto era) )
-> Set (SL.Credential 'HotCommitteeRole (EraCrypto era))
-> Set SL.MemberStatus
-> BlockQuery (ShelleyBlock proto era) (SL.CommitteeMembersState (EraCrypto era))
GetFilteredVoteDelegatees
:: CG.ConwayEraGov era
=> Set (SL.Credential 'SL.Staking (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (VoteDelegatees (EraCrypto era))
GetAccountState
:: BlockQuery (ShelleyBlock proto era) AccountState
GetSPOStakeDistr
:: CG.ConwayEraGov era
=> Set (KeyHash 'StakePool (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (Map (KeyHash 'StakePool (EraCrypto era)) Coin)
GetProposals
:: CG.ConwayEraGov era
=> Set (CG.GovActionId (EraCrypto era))
-> 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
instance (Typeable era, Typeable proto)
=> ShowProxy (BlockQuery (ShelleyBlock proto era)) where
instance (ShelleyCompatible proto era, ProtoCrypto proto ~ 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 (EraCrypto era)))
creds ->
Map
(Either Coin (Credential 'Staking crypto))
(Map (KeyHash 'StakePool crypto) Coin)
-> NonMyopicMemberRewards crypto
forall c.
Map
(Either Coin (Credential 'Staking c))
(Map (KeyHash 'StakePool c) Coin)
-> NonMyopicMemberRewards c
NonMyopicMemberRewards (Map
(Either Coin (Credential 'Staking crypto))
(Map (KeyHash 'StakePool crypto) Coin)
-> NonMyopicMemberRewards crypto)
-> Map
(Either Coin (Credential 'Staking crypto))
(Map (KeyHash 'StakePool crypto) Coin)
-> NonMyopicMemberRewards crypto
forall a b. (a -> b) -> a -> b
$
Globals
-> NewEpochState era
-> Set (Either Coin (Credential 'Staking (EraCrypto era)))
-> Map
(Either Coin (Credential 'Staking (EraCrypto era)))
(Map (KeyHash 'StakePool (EraCrypto era)) Coin)
forall era.
EraGov era =>
Globals
-> NewEpochState era
-> Set (Either Coin (Credential 'Staking (EraCrypto era)))
-> Map
(Either Coin (Credential 'Staking (EraCrypto era)))
(Map (KeyHash 'StakePool (EraCrypto era)) Coin)
SL.getNonMyopicMemberRewards Globals
globals NewEpochState era
st Set (Either Coin (Credential 'Staking (EraCrypto era)))
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 ->
NewEpochState era -> ProposedPPUpdates era
forall era.
ShelleyBasedEra era =>
NewEpochState era -> ProposedPPUpdates era
getProposedPPUpdates NewEpochState era
st
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakeDistribution ->
PoolDistr crypto -> PoolDistr crypto
forall c. PoolDistr c -> PoolDistr c
fromLedgerPoolDistr (PoolDistr crypto -> PoolDistr crypto)
-> PoolDistr crypto -> PoolDistr crypto
forall a b. (a -> b) -> a -> b
$ Globals -> NewEpochState era -> PoolDistr (EraCrypto era)
forall era.
EraGov era =>
Globals -> NewEpochState era -> PoolDistr (EraCrypto era)
SL.poolsByTotalStakeFraction Globals
globals NewEpochState era
st
GetUTxOByAddress Set (Addr (EraCrypto era))
addrs ->
NewEpochState era -> Set (Addr (EraCrypto era)) -> UTxO era
forall era.
EraTxOut era =>
NewEpochState era -> Set (Addr (EraCrypto era)) -> UTxO era
SL.getFilteredUTxO NewEpochState era
st Set (Addr (EraCrypto era))
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 (EraCrypto era))
creds ->
NewEpochState era
-> Set (Credential 'Staking (EraCrypto era))
-> (Delegations (EraCrypto era), RewardAccounts (EraCrypto era))
forall era.
NewEpochState era
-> Set (Credential 'Staking (EraCrypto era))
-> (Delegations (EraCrypto era), RewardAccounts (EraCrypto era))
getFilteredDelegationsAndRewardAccounts NewEpochState era
st Set (Credential 'Staking (EraCrypto era))
creds
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGenesisConfig ->
ShelleyLedgerConfig era -> CompactGenesis (EraCrypto era)
forall era.
ShelleyLedgerConfig era -> CompactGenesis (EraCrypto era)
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 crypto, result) -> result
forall a b. (a, b) -> b
snd ((RewardUpdate crypto, result) -> result)
-> (RewardUpdate crypto, result) -> result
forall a b. (a -> b) -> a -> b
$ Globals
-> NewEpochState era
-> (RewardUpdate (EraCrypto era), RewardProvenance (EraCrypto era))
forall era.
EraGov era =>
Globals
-> NewEpochState era
-> (RewardUpdate (EraCrypto era), RewardProvenance (EraCrypto era))
SL.getRewardProvenance Globals
globals NewEpochState era
st
GetUTxOByTxIn Set (TxIn (EraCrypto era))
txins ->
NewEpochState era -> Set (TxIn (EraCrypto era)) -> UTxO era
forall era.
NewEpochState era -> Set (TxIn (EraCrypto era)) -> UTxO era
SL.getUTxOSubset NewEpochState era
st Set (TxIn (EraCrypto era))
txins
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakePools ->
NewEpochState era -> Set (KeyHash 'StakePool (EraCrypto era))
forall era.
NewEpochState era -> Set (KeyHash 'StakePool (EraCrypto era))
SL.getPools NewEpochState era
st
GetStakePoolParams Set (KeyHash 'StakePool (EraCrypto era))
poolids ->
NewEpochState era
-> Set (KeyHash 'StakePool (EraCrypto era))
-> Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
forall era.
NewEpochState era
-> Set (KeyHash 'StakePool (EraCrypto era))
-> Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
SL.getPoolParameters NewEpochState era
st Set (KeyHash 'StakePool (EraCrypto era))
poolids
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardInfoPools ->
Globals
-> NewEpochState era
-> (RewardParams,
Map (KeyHash 'StakePool (EraCrypto era)) RewardInfoPool)
forall era.
EraGov era =>
Globals
-> NewEpochState era
-> (RewardParams,
Map (KeyHash 'StakePool (EraCrypto era)) RewardInfoPool)
SL.getRewardInfoPools Globals
globals NewEpochState era
st
GetPoolState Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
mPoolIds ->
let certPState :: PState era
certPState = CertState era -> PState era
forall era. CertState era -> PState era
SL.certPState (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 (EraCrypto era)))
mPoolIds of
Just Set (KeyHash 'StakePool (EraCrypto era))
poolIds ->
SL.PState
{ psStakePoolParams :: Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
SL.psStakePoolParams =
Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
-> Set (KeyHash 'StakePool (EraCrypto era))
-> Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys (PState era
-> Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
forall era.
PState era
-> Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
SL.psStakePoolParams PState era
certPState) Set (KeyHash 'StakePool (EraCrypto era))
poolIds
, psFutureStakePoolParams :: Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
SL.psFutureStakePoolParams =
Map (KeyHash 'StakePool crypto) (PoolParams crypto)
-> Set (KeyHash 'StakePool crypto)
-> Map (KeyHash 'StakePool crypto) (PoolParams crypto)
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys (PState era
-> Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
forall era.
PState era
-> Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
SL.psFutureStakePoolParams PState era
certPState) Set (KeyHash 'StakePool crypto)
Set (KeyHash 'StakePool (EraCrypto era))
poolIds
, psRetiring :: Map (KeyHash 'StakePool (EraCrypto era)) EpochNo
SL.psRetiring = Map (KeyHash 'StakePool crypto) EpochNo
-> Set (KeyHash 'StakePool crypto)
-> Map (KeyHash 'StakePool crypto) EpochNo
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys (PState era -> Map (KeyHash 'StakePool (EraCrypto era)) EpochNo
forall era.
PState era -> Map (KeyHash 'StakePool (EraCrypto era)) EpochNo
SL.psRetiring PState era
certPState) Set (KeyHash 'StakePool crypto)
Set (KeyHash 'StakePool (EraCrypto era))
poolIds
, psDeposits :: Map (KeyHash 'StakePool (EraCrypto era)) Coin
SL.psDeposits = Map (KeyHash 'StakePool crypto) Coin
-> Set (KeyHash 'StakePool crypto)
-> Map (KeyHash 'StakePool crypto) Coin
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys (PState era -> Map (KeyHash 'StakePool (EraCrypto era)) Coin
forall era.
PState era -> Map (KeyHash 'StakePool (EraCrypto era)) Coin
SL.psDeposits PState era
certPState) Set (KeyHash 'StakePool crypto)
Set (KeyHash 'StakePool (EraCrypto era))
poolIds
}
Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
Nothing -> result
PState era
certPState
GetStakeSnapshots Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
mPoolIds ->
let SL.SnapShots
{ SnapShot crypto
ssStakeMark :: SnapShot crypto
$sel:ssStakeMark:SnapShots :: forall c. SnapShots c -> SnapShot c
SL.ssStakeMark
, SnapShot crypto
ssStakeSet :: SnapShot crypto
$sel:ssStakeSet:SnapShots :: forall c. SnapShots c -> SnapShot c
SL.ssStakeSet
, SnapShot crypto
ssStakeGo :: SnapShot crypto
$sel:ssStakeGo:SnapShots :: forall c. SnapShots c -> SnapShot c
SL.ssStakeGo
} = EpochState era -> SnapShots crypto
EpochState era -> SnapShots (EraCrypto era)
forall era. EpochState era -> SnapShots (EraCrypto era)
SL.esSnapshots (EpochState era -> SnapShots crypto)
-> (NewEpochState era -> EpochState era)
-> NewEpochState era
-> SnapShots crypto
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 crypto)
-> NewEpochState era -> SnapShots crypto
forall a b. (a -> b) -> a -> b
$ NewEpochState era
st
totalMarkByPoolId :: Map (KeyHash 'StakePool crypto) Coin
totalMarkByPoolId :: Map (KeyHash 'StakePool crypto) Coin
totalMarkByPoolId = VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Stake crypto -> Map (KeyHash 'StakePool crypto) Coin
forall c.
VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c)
-> Stake c -> Map (KeyHash 'StakePool c) Coin
SL.sumStakePerPool (SnapShot crypto
-> VMap
VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
forall c.
SnapShot c
-> VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c)
SL.ssDelegations SnapShot crypto
ssStakeMark) (SnapShot crypto -> Stake crypto
forall c. SnapShot c -> Stake c
SL.ssStake SnapShot crypto
ssStakeMark)
totalSetByPoolId :: Map (KeyHash 'StakePool crypto) Coin
totalSetByPoolId :: Map (KeyHash 'StakePool crypto) Coin
totalSetByPoolId = VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Stake crypto -> Map (KeyHash 'StakePool crypto) Coin
forall c.
VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c)
-> Stake c -> Map (KeyHash 'StakePool c) Coin
SL.sumStakePerPool (SnapShot crypto
-> VMap
VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
forall c.
SnapShot c
-> VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c)
SL.ssDelegations SnapShot crypto
ssStakeSet) (SnapShot crypto -> Stake crypto
forall c. SnapShot c -> Stake c
SL.ssStake SnapShot crypto
ssStakeSet)
totalGoByPoolId :: Map (KeyHash 'StakePool crypto) Coin
totalGoByPoolId :: Map (KeyHash 'StakePool crypto) Coin
totalGoByPoolId = VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> Stake crypto -> Map (KeyHash 'StakePool crypto) Coin
forall c.
VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c)
-> Stake c -> Map (KeyHash 'StakePool c) Coin
SL.sumStakePerPool (SnapShot crypto
-> VMap
VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
forall c.
SnapShot c
-> VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c)
SL.ssDelegations SnapShot crypto
ssStakeGo) (SnapShot crypto -> Stake crypto
forall c. SnapShot c -> Stake c
SL.ssStake SnapShot crypto
ssStakeGo)
getPoolStakes :: Set (KeyHash 'StakePool crypto) -> Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
getPoolStakes :: Set (KeyHash 'StakePool crypto)
-> Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
getPoolStakes Set (KeyHash 'StakePool crypto)
poolIds = (KeyHash 'StakePool crypto -> StakeSnapshot crypto)
-> Set (KeyHash 'StakePool crypto)
-> Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
forall k a. (k -> a) -> Set k -> Map k a
Map.fromSet KeyHash 'StakePool crypto -> StakeSnapshot crypto
mkStakeSnapshot Set (KeyHash 'StakePool crypto)
poolIds
where mkStakeSnapshot :: KeyHash 'StakePool crypto -> StakeSnapshot crypto
mkStakeSnapshot KeyHash 'StakePool crypto
poolId = StakeSnapshot
{ ssMarkPool :: Coin
ssMarkPool = Coin
-> KeyHash 'StakePool crypto
-> Map (KeyHash 'StakePool crypto) Coin
-> Coin
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault Coin
forall a. Monoid a => a
mempty KeyHash 'StakePool crypto
poolId Map (KeyHash 'StakePool crypto) Coin
totalMarkByPoolId
, ssSetPool :: Coin
ssSetPool = Coin
-> KeyHash 'StakePool crypto
-> Map (KeyHash 'StakePool crypto) Coin
-> Coin
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault Coin
forall a. Monoid a => a
mempty KeyHash 'StakePool crypto
poolId Map (KeyHash 'StakePool crypto) Coin
totalSetByPoolId
, ssGoPool :: Coin
ssGoPool = Coin
-> KeyHash 'StakePool crypto
-> Map (KeyHash 'StakePool crypto) Coin
-> Coin
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault Coin
forall a. Monoid a => a
mempty KeyHash 'StakePool crypto
poolId Map (KeyHash 'StakePool crypto) Coin
totalGoByPoolId
}
getAllStake :: SL.SnapShot crypto -> SL.Coin
getAllStake :: SnapShot crypto -> Coin
getAllStake (SL.SnapShot Stake crypto
stake VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
_ VMap VB VB (KeyHash 'StakePool crypto) (PoolParams crypto)
_) = (CompactForm Coin -> Coin)
-> VMap VB VP (Credential 'Staking crypto) (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 crypto
-> VMap VB VP (Credential 'Staking crypto) (CompactForm Coin)
forall c.
Stake c -> VMap VB VP (Credential 'Staking c) (CompactForm Coin)
SL.unStake Stake crypto
stake)
in
case Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
mPoolIds of
Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
Nothing ->
let poolIds :: Set (KeyHash 'StakePool crypto)
poolIds = [KeyHash 'StakePool crypto] -> Set (KeyHash 'StakePool crypto)
forall a. Ord a => [a] -> Set a
Set.fromList ([KeyHash 'StakePool crypto] -> Set (KeyHash 'StakePool crypto))
-> [KeyHash 'StakePool crypto] -> Set (KeyHash 'StakePool crypto)
forall a b. (a -> b) -> a -> b
$ [[KeyHash 'StakePool crypto]] -> [KeyHash 'StakePool crypto]
forall a. Monoid a => [a] -> a
mconcat
[ VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> [KeyHash 'StakePool crypto]
forall (vv :: * -> *) v (kv :: * -> *) k.
Vector vv v =>
VMap kv vv k v -> [v]
VMap.elems (SnapShot crypto
-> VMap
VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
forall c.
SnapShot c
-> VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c)
SL.ssDelegations SnapShot crypto
ssStakeMark)
, VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> [KeyHash 'StakePool crypto]
forall (vv :: * -> *) v (kv :: * -> *) k.
Vector vv v =>
VMap kv vv k v -> [v]
VMap.elems (SnapShot crypto
-> VMap
VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
forall c.
SnapShot c
-> VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c)
SL.ssDelegations SnapShot crypto
ssStakeSet)
, VMap VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
-> [KeyHash 'StakePool crypto]
forall (vv :: * -> *) v (kv :: * -> *) k.
Vector vv v =>
VMap kv vv k v -> [v]
VMap.elems (SnapShot crypto
-> VMap
VB VB (Credential 'Staking crypto) (KeyHash 'StakePool crypto)
forall c.
SnapShot c
-> VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c)
SL.ssDelegations SnapShot crypto
ssStakeGo)
]
in
StakeSnapshots
{ ssStakeSnapshots :: Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
ssStakeSnapshots = Set (KeyHash 'StakePool crypto)
-> Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
getPoolStakes Set (KeyHash 'StakePool crypto)
poolIds
, ssMarkTotal :: Coin
ssMarkTotal = SnapShot crypto -> Coin
getAllStake SnapShot crypto
ssStakeMark
, ssSetTotal :: Coin
ssSetTotal = SnapShot crypto -> Coin
getAllStake SnapShot crypto
ssStakeSet
, ssGoTotal :: Coin
ssGoTotal = SnapShot crypto -> Coin
getAllStake SnapShot crypto
ssStakeGo
}
Just Set (KeyHash 'StakePool (EraCrypto era))
poolIds ->
StakeSnapshots
{ ssStakeSnapshots :: Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
ssStakeSnapshots = Set (KeyHash 'StakePool crypto)
-> Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
getPoolStakes Set (KeyHash 'StakePool crypto)
Set (KeyHash 'StakePool (EraCrypto era))
poolIds
, ssMarkTotal :: Coin
ssMarkTotal = SnapShot crypto -> Coin
getAllStake SnapShot crypto
ssStakeMark
, ssSetTotal :: Coin
ssSetTotal = SnapShot crypto -> Coin
getAllStake SnapShot crypto
ssStakeSet
, ssGoTotal :: Coin
ssGoTotal = SnapShot crypto -> Coin
getAllStake SnapShot crypto
ssStakeGo
}
GetPoolDistr Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
mPoolIds ->
let stakeSet :: SnapShot crypto
stakeSet = SnapShots crypto -> SnapShot crypto
forall c. SnapShots c -> SnapShot c
SL.ssStakeSet (SnapShots crypto -> SnapShot crypto)
-> (EpochState era -> SnapShots crypto)
-> EpochState era
-> SnapShot crypto
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EpochState era -> SnapShots crypto
EpochState era -> SnapShots (EraCrypto era)
forall era. EpochState era -> SnapShots (EraCrypto era)
SL.esSnapshots (EpochState era -> SnapShot crypto)
-> EpochState era -> SnapShot crypto
forall a b. (a -> b) -> a -> b
$ NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
getEpochState NewEpochState era
st in
PoolDistr crypto -> PoolDistr crypto
forall c. PoolDistr c -> PoolDistr c
fromLedgerPoolDistr (PoolDistr crypto -> PoolDistr crypto)
-> PoolDistr crypto -> PoolDistr crypto
forall a b. (a -> b) -> a -> b
$
(KeyHash 'StakePool crypto -> Bool)
-> SnapShot crypto -> PoolDistr crypto
forall c.
(KeyHash 'StakePool c -> Bool) -> SnapShot c -> PoolDistr c
SL.calculatePoolDistr' ((KeyHash 'StakePool crypto -> Bool)
-> (Set (KeyHash 'StakePool crypto)
-> KeyHash 'StakePool crypto -> Bool)
-> Maybe (Set (KeyHash 'StakePool crypto))
-> KeyHash 'StakePool crypto
-> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Bool -> KeyHash 'StakePool crypto -> Bool
forall a b. a -> b -> a
const Bool
True) ((KeyHash 'StakePool crypto
-> Set (KeyHash 'StakePool crypto) -> Bool)
-> Set (KeyHash 'StakePool crypto)
-> KeyHash 'StakePool crypto
-> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip KeyHash 'StakePool crypto
-> Set (KeyHash 'StakePool crypto) -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member) Maybe (Set (KeyHash 'StakePool crypto))
Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
mPoolIds) SnapShot crypto
stakeSet
GetStakeDelegDeposits Set (Credential 'Staking (EraCrypto era))
stakeCreds ->
let lookupDeposit :: Credential 'Staking (EraCrypto era) -> Maybe Coin
lookupDeposit =
DState era -> Credential 'Staking (EraCrypto era) -> Maybe Coin
forall era.
DState era -> StakeCredential (EraCrypto era) -> Maybe Coin
lookupDepositDState (CertState era -> DState era
forall era. CertState era -> DState era
SL.certDState (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 :: RewardAccounts crypto
-> Credential 'Staking crypto -> RewardAccounts crypto
lookupInsert RewardAccounts crypto
acc Credential 'Staking crypto
cred =
case Credential 'Staking (EraCrypto era) -> Maybe Coin
lookupDeposit Credential 'Staking crypto
Credential 'Staking (EraCrypto era)
cred of
Maybe Coin
Nothing -> RewardAccounts crypto
acc
Just Coin
deposit -> Credential 'Staking crypto
-> Coin -> RewardAccounts crypto -> RewardAccounts crypto
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Credential 'Staking crypto
cred Coin
deposit RewardAccounts crypto
acc
in (result -> Credential 'Staking crypto -> result)
-> result -> Set (Credential 'Staking crypto) -> result
forall a b. (a -> b -> a) -> a -> Set b -> a
Set.foldl' result -> Credential 'Staking crypto -> result
RewardAccounts crypto
-> Credential 'Staking crypto -> RewardAccounts crypto
lookupInsert result
RewardAccounts crypto
forall k a. Map k a
Map.empty Set (Credential 'Staking crypto)
Set (Credential 'Staking (EraCrypto era))
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 (EraCrypto era))
drepCreds ->
NewEpochState era
-> Set (Credential 'DRepRole (EraCrypto era))
-> Map
(Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
forall era.
NewEpochState era
-> Set (Credential 'DRepRole (EraCrypto era))
-> Map
(Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
SL.queryDRepState NewEpochState era
st Set (Credential 'DRepRole (EraCrypto era))
drepCreds
GetDRepStakeDistr Set (DRep (EraCrypto era))
dreps ->
NewEpochState era
-> Set (DRep (EraCrypto era)) -> Map (DRep (EraCrypto era)) Coin
forall era.
ConwayEraGov era =>
NewEpochState era
-> Set (DRep (EraCrypto era)) -> Map (DRep (EraCrypto era)) Coin
SL.queryDRepStakeDistr NewEpochState era
st Set (DRep (EraCrypto era))
dreps
GetCommitteeMembersState Set (Credential 'ColdCommitteeRole (EraCrypto era))
coldCreds Set (Credential 'HotCommitteeRole (EraCrypto era))
hotCreds Set MemberStatus
statuses ->
Set (Credential 'ColdCommitteeRole (EraCrypto era))
-> Set (Credential 'HotCommitteeRole (EraCrypto era))
-> Set MemberStatus
-> NewEpochState era
-> CommitteeMembersState (EraCrypto era)
forall era.
ConwayEraGov era =>
Set (Credential 'ColdCommitteeRole (EraCrypto era))
-> Set (Credential 'HotCommitteeRole (EraCrypto era))
-> Set MemberStatus
-> NewEpochState era
-> CommitteeMembersState (EraCrypto era)
SL.queryCommitteeMembersState Set (Credential 'ColdCommitteeRole (EraCrypto era))
coldCreds Set (Credential 'HotCommitteeRole (EraCrypto era))
hotCreds Set MemberStatus
statuses NewEpochState era
st
GetFilteredVoteDelegatees Set (Credential 'Staking (EraCrypto era))
stakeCreds ->
NewEpochState era
-> Set (Credential 'Staking (EraCrypto era))
-> Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
forall era.
NewEpochState era
-> Set (Credential 'Staking (EraCrypto era))
-> VoteDelegatees (EraCrypto era)
getFilteredVoteDelegatees NewEpochState era
st Set (Credential 'Staking (EraCrypto era))
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 (EraCrypto era))
keys ->
NewEpochState era
-> Set (KeyHash 'StakePool (EraCrypto era))
-> Map (KeyHash 'StakePool (EraCrypto era)) Coin
forall era.
ConwayEraGov era =>
NewEpochState era
-> Set (KeyHash 'StakePool (EraCrypto era))
-> Map (KeyHash 'StakePool (EraCrypto era)) Coin
SL.querySPOStakeDistr NewEpochState era
st Set (KeyHash 'StakePool (EraCrypto era))
keys
GetProposals Set (GovActionId (EraCrypto era))
gids ->
NewEpochState era
-> Set (GovActionId (EraCrypto era)) -> Seq (GovActionState era)
forall era.
ConwayEraGov era =>
NewEpochState era
-> Set (GovActionId (EraCrypto era)) -> Seq (GovActionState era)
SL.queryProposals NewEpochState era
st Set (GovActionId (EraCrypto era))
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)
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
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 (EraCrypto era)))
creds) (GetNonMyopicMemberRewards Set (Either Coin (Credential 'Staking (EraCrypto era)))
creds')
| Set (Either Coin (Credential 'Staking (EraCrypto era)))
creds Set (Either Coin (Credential 'Staking (EraCrypto era)))
-> Set (Either Coin (Credential 'Staking (EraCrypto era))) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (Either Coin (Credential 'Staking (EraCrypto era)))
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 (EraCrypto era)))
_) 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 (EraCrypto era))
addrs) (GetUTxOByAddress Set (Addr (EraCrypto era))
addrs')
| Set (Addr (EraCrypto era))
addrs Set (Addr (EraCrypto era)) -> Set (Addr (EraCrypto era)) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (Addr (EraCrypto era))
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 (EraCrypto era))
_) 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 (EraCrypto era))
creds)
(GetFilteredDelegationsAndRewardAccounts Set (Credential 'Staking (EraCrypto era))
creds')
| Set (Credential 'Staking (EraCrypto era))
creds Set (Credential 'Staking (EraCrypto era))
-> Set (Credential 'Staking (EraCrypto era)) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (Credential 'Staking (EraCrypto era))
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 (EraCrypto era))
_) 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 (EraCrypto era))
addrs) (GetUTxOByTxIn Set (TxIn (EraCrypto era))
addrs')
| Set (TxIn (EraCrypto era))
addrs Set (TxIn (EraCrypto era)) -> Set (TxIn (EraCrypto era)) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (TxIn (EraCrypto era))
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 (EraCrypto era))
_) 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 (EraCrypto era))
poolids) (GetStakePoolParams Set (KeyHash 'StakePool (EraCrypto era))
poolids')
| Set (KeyHash 'StakePool (EraCrypto era))
poolids Set (KeyHash 'StakePool (EraCrypto era))
-> Set (KeyHash 'StakePool (EraCrypto era)) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (KeyHash 'StakePool (EraCrypto era))
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 (EraCrypto era))
_) 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 (EraCrypto era)))
poolids) (GetPoolState Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolids')
| Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolids Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> Maybe (Set (KeyHash 'StakePool (EraCrypto era))) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
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 (EraCrypto era)))
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetStakeSnapshots Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolid) (GetStakeSnapshots Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolid')
| Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolid Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> Maybe (Set (KeyHash 'StakePool (EraCrypto era))) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
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 (EraCrypto era)))
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetPoolDistr Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolids) (GetPoolDistr Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolids')
| Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolids Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> Maybe (Set (KeyHash 'StakePool (EraCrypto era))) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
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 (EraCrypto era)))
_) BlockQuery (ShelleyBlock proto era) b
_
= Maybe (a :~: b)
forall a. Maybe a
Nothing
sameDepIndex (GetStakeDelegDeposits Set (Credential 'Staking (EraCrypto era))
stakeCreds) (GetStakeDelegDeposits Set (Credential 'Staking (EraCrypto era))
stakeCreds')
| Set (Credential 'Staking (EraCrypto era))
stakeCreds Set (Credential 'Staking (EraCrypto era))
-> Set (Credential 'Staking (EraCrypto era)) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (Credential 'Staking (EraCrypto era))
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 (EraCrypto era))
_) 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 (EraCrypto era))
stakeCreds) (GetFilteredVoteDelegatees Set (Credential 'Staking (EraCrypto era))
stakeCreds')
| Set (Credential 'Staking (EraCrypto era))
stakeCreds Set (Credential 'Staking (EraCrypto era))
-> Set (Credential 'Staking (EraCrypto era)) -> Bool
forall a. Eq a => a -> a -> Bool
== Set (Credential 'Staking (EraCrypto era))
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
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
querySupportedVersion :: BlockQuery (ShelleyBlock proto era) result -> ShelleyNodeToClientVersion -> Bool
querySupportedVersion :: forall proto era result.
BlockQuery (ShelleyBlock proto era) result
-> ShelleyNodeToClientVersion -> Bool
querySupportedVersion = \case
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetLedgerTip -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetEpochNo -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
GetNonMyopicMemberRewards {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetCurrentPParams -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetProposedPParamsUpdates -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakeDistribution -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
GetUTxOByAddress {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetUTxOWhole -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugEpochState -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
GetCBOR BlockQuery (ShelleyBlock proto era) result
q -> BlockQuery (ShelleyBlock proto era) result
-> ShelleyNodeToClientVersion -> Bool
forall proto era result.
BlockQuery (ShelleyBlock proto era) result
-> ShelleyNodeToClientVersion -> Bool
querySupportedVersion BlockQuery (ShelleyBlock proto era) result
q
GetFilteredDelegationsAndRewardAccounts {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v1)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetGenesisConfig -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v2)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugNewEpochState -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v2)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
DebugChainDepState -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v2)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardProvenance -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v3)
GetUTxOByTxIn {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v4)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetStakePools -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v4)
GetStakePoolParams {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v4)
BlockQuery (ShelleyBlock proto era) result
R:BlockQueryShelleyBlock proto era result
GetRewardInfoPools -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v5)
GetPoolState {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v6)
GetStakeSnapshots {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v6)
GetPoolDistr {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v6)
GetStakeDelegDeposits {} -> (ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
v7)
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)
where
v1 :: ShelleyNodeToClientVersion
v1 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion1
v2 :: ShelleyNodeToClientVersion
v2 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion2
v3 :: ShelleyNodeToClientVersion
v3 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion3
v4 :: ShelleyNodeToClientVersion
v4 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion4
v5 :: ShelleyNodeToClientVersion
v5 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion5
v6 :: ShelleyNodeToClientVersion
v6 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion6
v7 :: ShelleyNodeToClientVersion
v7 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion7
v8 :: ShelleyNodeToClientVersion
v8 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion8
v9 :: ShelleyNodeToClientVersion
v9 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion9
v10 :: ShelleyNodeToClientVersion
v10 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion10
v11 :: ShelleyNodeToClientVersion
v11 = ShelleyNodeToClientVersion
ShelleyNodeToClientVersion11
getProposedPPUpdates ::
ShelleyBasedEra era
=> SL.NewEpochState era -> SL.ProposedPPUpdates era
getProposedPPUpdates :: forall era.
ShelleyBasedEra era =>
NewEpochState era -> ProposedPPUpdates era
getProposedPPUpdates =
ProposedPPUpdates era
-> Maybe (ProposedPPUpdates era) -> ProposedPPUpdates era
forall a. a -> Maybe a -> a
fromMaybe ProposedPPUpdates era
forall era. ProposedPPUpdates era
SL.emptyPPPUpdates
(Maybe (ProposedPPUpdates era) -> ProposedPPUpdates era)
-> (NewEpochState era -> Maybe (ProposedPPUpdates era))
-> NewEpochState era
-> ProposedPPUpdates era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GovState era -> Maybe (ProposedPPUpdates era)
forall era.
EraGov era =>
GovState era -> Maybe (ProposedPPUpdates era)
LC.getProposedPPUpdates
(GovState era -> Maybe (ProposedPPUpdates era))
-> (NewEpochState era -> GovState era)
-> NewEpochState era
-> Maybe (ProposedPPUpdates era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (GovState era) (NewEpochState era) (GovState era)
-> NewEpochState era -> GovState era
forall a s. Getting a s a -> s -> a
view Getting (GovState era) (NewEpochState era) (GovState era)
forall era (f :: * -> *).
Functor f =>
(GovState era -> f (GovState era))
-> NewEpochState era -> f (NewEpochState era)
SL.newEpochStateGovStateL
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.NewEpochState era -> SL.DState era
getDState :: forall era. NewEpochState era -> DState era
getDState = CertState era -> DState era
forall era. CertState era -> DState era
SL.certDState (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.NewEpochState era
-> Set (SL.Credential 'SL.Staking (EraCrypto era))
-> (Delegations (EraCrypto era), SL.RewardAccounts (EraCrypto era))
getFilteredDelegationsAndRewardAccounts :: forall era.
NewEpochState era
-> Set (Credential 'Staking (EraCrypto era))
-> (Delegations (EraCrypto era), RewardAccounts (EraCrypto era))
getFilteredDelegationsAndRewardAccounts NewEpochState era
ss Set (Credential 'Staking (EraCrypto era))
creds =
(Map
(Credential 'Staking (EraCrypto era))
(KeyHash 'StakePool (EraCrypto era))
filteredDelegations, Map (Credential 'Staking (EraCrypto era)) Coin
filteredRwdAcnts)
where
UMap Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
umElems Map Ptr (Credential 'Staking (EraCrypto era))
_ = DState era -> UMap (EraCrypto era)
forall era. DState era -> UMap (EraCrypto era)
SL.dsUnified (DState era -> UMap (EraCrypto era))
-> DState era -> UMap (EraCrypto era)
forall a b. (a -> b) -> a -> b
$ NewEpochState era -> DState era
forall era. NewEpochState era -> DState era
getDState NewEpochState era
ss
umElemsRestricted :: Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
umElemsRestricted = Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
-> Set (Credential 'Staking (EraCrypto era))
-> Map
(Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
umElems Set (Credential 'Staking (EraCrypto era))
creds
filteredDelegations :: Map
(Credential 'Staking (EraCrypto era))
(KeyHash 'StakePool (EraCrypto era))
filteredDelegations = (UMElem (EraCrypto era)
-> Maybe (KeyHash 'StakePool (EraCrypto era)))
-> Map
(Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
-> Map
(Credential 'Staking (EraCrypto era))
(KeyHash 'StakePool (EraCrypto era))
forall a b k. (a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybe UMElem (EraCrypto era)
-> Maybe (KeyHash 'StakePool (EraCrypto era))
forall c. UMElem c -> Maybe (KeyHash 'StakePool c)
umElemSPool Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
umElemsRestricted
filteredRwdAcnts :: Map (Credential 'Staking (EraCrypto era)) Coin
filteredRwdAcnts =
(UMElem (EraCrypto era) -> Maybe Coin)
-> Map
(Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
-> Map (Credential 'Staking (EraCrypto era)) Coin
forall a b k. (a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybe (\UMElem (EraCrypto era)
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 (EraCrypto era) -> Maybe RDPair
forall c. UMElem c -> Maybe RDPair
umElemRDPair UMElem (EraCrypto era)
e) Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
umElemsRestricted
getFilteredVoteDelegatees ::
SL.NewEpochState era
-> Set (SL.Credential 'SL.Staking (EraCrypto era))
-> VoteDelegatees (EraCrypto era)
getFilteredVoteDelegatees :: forall era.
NewEpochState era
-> Set (Credential 'Staking (EraCrypto era))
-> VoteDelegatees (EraCrypto era)
getFilteredVoteDelegatees NewEpochState era
ss Set (Credential 'Staking (EraCrypto era))
creds = (UMElem (EraCrypto era) -> Maybe (DRep (EraCrypto era)))
-> Map
(Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
-> Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
forall a b k. (a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybe UMElem (EraCrypto era) -> Maybe (DRep (EraCrypto era))
forall c. UMElem c -> Maybe (DRep c)
umElemDRep Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
umElemsRestricted
where
UMap Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
umElems Map Ptr (Credential 'Staking (EraCrypto era))
_ = DState era -> UMap (EraCrypto era)
forall era. DState era -> UMap (EraCrypto era)
SL.dsUnified (DState era -> UMap (EraCrypto era))
-> DState era -> UMap (EraCrypto era)
forall a b. (a -> b) -> a -> b
$ NewEpochState era -> DState era
forall era. NewEpochState era -> DState era
getDState NewEpochState era
ss
umElemsRestricted :: Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
umElemsRestricted = Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
-> Set (Credential 'Staking (EraCrypto era))
-> Map
(Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
forall k a. Ord k => Map k a -> Set k -> Map k a
Map.restrictKeys Map (Credential 'Staking (EraCrypto era)) (UMElem (EraCrypto era))
umElems Set (Credential 'Staking (EraCrypto era))
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 (EraCrypto era)))
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 (EraCrypto era))) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Either Coin (Credential 'Staking (EraCrypto era)))
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 (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era)) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (KeyHash 'StakePool (EraCrypto era))
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 (EraCrypto era)))
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 (EraCrypto era))) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolids
GetStakeSnapshots Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
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 (EraCrypto era))) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolId
GetPoolDistr Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
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 (EraCrypto era))) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
poolids
GetStakeDelegDeposits Set (Credential 'Staking (EraCrypto era))
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 (EraCrypto era)) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Credential 'Staking (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era)) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Credential 'DRepRole (EraCrypto era))
drepCreds
GetDRepStakeDistr Set (DRep (EraCrypto era))
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 (EraCrypto era))
dreps
GetCommitteeMembersState Set (Credential 'ColdCommitteeRole (EraCrypto era))
coldCreds Set (Credential 'HotCommitteeRole (EraCrypto era))
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 (EraCrypto era)) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Credential 'ColdCommitteeRole (EraCrypto era))
coldCreds Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Set (Credential 'HotCommitteeRole (EraCrypto era)) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Set (Credential 'HotCommitteeRole (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era))
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 (EraCrypto era))
keys
GetProposals Set (GovActionId (EraCrypto era))
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 (EraCrypto era))
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
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 (EraCrypto 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) (NonMyopicMemberRewards (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Either Coin (Credential 'Staking (EraCrypto era)))
-> BlockQuery
(ShelleyBlock proto era) (NonMyopicMemberRewards (EraCrypto era)))
-> Set (Either Coin (Credential 'Staking (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Either Coin (Credential 'Staking (EraCrypto era)))
-> BlockQuery
(ShelleyBlock proto era) (NonMyopicMemberRewards (EraCrypto era))
forall era proto.
Set (Either Coin (Credential 'Staking (EraCrypto era)))
-> BlockQuery
(ShelleyBlock proto era) (NonMyopicMemberRewards (EraCrypto era))
GetNonMyopicMemberRewards (Set (Either Coin (Credential 'Staking (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder
s (Set (Either Coin (Credential 'Staking (EraCrypto era))))
-> 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 (EraCrypto era))))
forall s.
Decoder s (Set (Either Coin (Credential 'Staking (EraCrypto era))))
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 (EraCrypto 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) (PoolDistr (EraCrypto era))
forall proto era.
BlockQuery (ShelleyBlock proto era) (PoolDistr (EraCrypto era))
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 (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (UTxO era))
-> Set (Addr (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Addr (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (UTxO era)
forall era proto.
Set (Addr (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (UTxO era)
GetUTxOByAddress (Set (Addr (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Addr (EraCrypto era)))
-> 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 (EraCrypto era), RewardAccounts (EraCrypto 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)
(Delegations (EraCrypto era), RewardAccounts (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Delegations (EraCrypto era), RewardAccounts (EraCrypto era)))
-> Set (Credential 'Staking (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Delegations (EraCrypto era), RewardAccounts (EraCrypto era))
forall era proto.
Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Delegations (EraCrypto era), RewardAccounts (EraCrypto era))
GetFilteredDelegationsAndRewardAccounts (Set (Credential 'Staking (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Credential 'Staking (EraCrypto era)))
-> 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 (EraCrypto 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) (CompactGenesis (EraCrypto era))
forall proto era.
BlockQuery
(ShelleyBlock proto era) (CompactGenesis (EraCrypto era))
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 (EraCrypto 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) (RewardProvenance (EraCrypto era))
forall proto era.
BlockQuery
(ShelleyBlock proto era) (RewardProvenance (EraCrypto era))
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 (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (UTxO era))
-> Set (TxIn (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (TxIn (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (UTxO era)
forall era proto.
Set (TxIn (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (UTxO era)
GetUTxOByTxIn (Set (TxIn (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (TxIn (EraCrypto era)))
-> 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 (EraCrypto 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) (Set (KeyHash 'StakePool (EraCrypto era)))
forall proto era.
BlockQuery
(ShelleyBlock proto era) (Set (KeyHash 'StakePool (EraCrypto era)))
GetStakePools
(Int
2, Word8
17) -> BlockQuery
(ShelleyBlock proto era)
(Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto 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)
(Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (KeyHash 'StakePool (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))))
-> Set (KeyHash 'StakePool (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (KeyHash 'StakePool (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era)))
forall era proto.
Set (KeyHash 'StakePool (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era)))
GetStakePoolParams (Set (KeyHash 'StakePool (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (KeyHash 'StakePool (EraCrypto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Set (KeyHash 'StakePool (EraCrypto era)))
forall s. Decoder s (Set (KeyHash 'StakePool (EraCrypto era)))
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 (EraCrypto era)) 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 (EraCrypto era)) RewardInfoPool)
forall proto era.
BlockQuery
(ShelleyBlock proto era)
(RewardParams,
Map (KeyHash 'StakePool (EraCrypto era)) 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 (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era) (PState era))
-> Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era) (PState era)
forall era proto.
Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era) (PState era)
GetPoolState (Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Maybe (Set (KeyHash 'StakePool (EraCrypto era))))
-> 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 (EraCrypto era))))
forall s.
Decoder s (Maybe (Set (KeyHash 'StakePool (EraCrypto era))))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
2, Word8
20) -> BlockQuery
(ShelleyBlock proto era) (StakeSnapshots (EraCrypto 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) (StakeSnapshots (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> BlockQuery
(ShelleyBlock proto era) (StakeSnapshots (EraCrypto era)))
-> Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> BlockQuery
(ShelleyBlock proto era) (StakeSnapshots (EraCrypto era))
forall era proto.
Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> BlockQuery
(ShelleyBlock proto era) (StakeSnapshots (EraCrypto era))
GetStakeSnapshots (Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Maybe (Set (KeyHash 'StakePool (EraCrypto era))))
-> 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 (EraCrypto era))))
forall s.
Decoder s (Maybe (Set (KeyHash 'StakePool (EraCrypto era))))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
2, Word8
21) -> BlockQuery (ShelleyBlock proto era) (PoolDistr (EraCrypto 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) (PoolDistr (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era) (PoolDistr (EraCrypto era)))
-> Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era) (PoolDistr (EraCrypto era))
forall era proto.
Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> BlockQuery (ShelleyBlock proto era) (PoolDistr (EraCrypto era))
GetPoolDistr (Maybe (Set (KeyHash 'StakePool (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Maybe (Set (KeyHash 'StakePool (EraCrypto era))))
-> 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 (EraCrypto era))))
forall s.
Decoder s (Maybe (Set (KeyHash 'StakePool (EraCrypto era))))
forall a s. FromCBOR a => Decoder s a
fromCBOR
(Int
2, Word8
22) -> BlockQuery
(ShelleyBlock proto era) (RewardAccounts (EraCrypto 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) (RewardAccounts (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era) (RewardAccounts (EraCrypto era)))
-> Set (Credential 'Staking (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era) (RewardAccounts (EraCrypto era))
forall era proto.
Set (StakeCredential (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map (StakeCredential (EraCrypto era)) Coin)
GetStakeDelegDeposits (Set (Credential 'Staking (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Credential 'Staking (EraCrypto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Set (Credential 'Staking (EraCrypto era)))
forall s. Decoder s (Set (Credential 'Staking (EraCrypto era)))
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 (EraCrypto era)) (DRepState (EraCrypto 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)
(Map
(Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era)))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Credential 'DRepRole (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map
(Credential 'DRepRole (EraCrypto era))
(DRepState (EraCrypto era))))
-> Set (Credential 'DRepRole (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Credential 'DRepRole (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map
(Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era)))
forall era proto.
ConwayEraGov era =>
Set (Credential 'DRepRole (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map
(Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era)))
GetDRepState (Set (Credential 'DRepRole (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Credential 'DRepRole (EraCrypto era)))
-> Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Set (Credential 'DRepRole (EraCrypto era)))
forall s. Decoder s (Set (Credential 'DRepRole (EraCrypto era)))
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 (EraCrypto era)) 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 (EraCrypto era)) Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (DRep (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era) (Map (DRep (EraCrypto era)) Coin))
-> Set (DRep (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (DRep (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era) (Map (DRep (EraCrypto era)) Coin)
forall era proto.
ConwayEraGov era =>
Set (DRep (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era) (Map (DRep (EraCrypto era)) Coin)
GetDRepStakeDistr (Set (DRep (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (DRep (EraCrypto era)))
-> 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 (EraCrypto era))
coldCreds <- Decoder s (Set (Credential 'ColdCommitteeRole (EraCrypto era)))
forall s.
Decoder s (Set (Credential 'ColdCommitteeRole (EraCrypto era)))
forall a s. FromCBOR a => Decoder s a
fromCBOR
Set (Credential 'HotCommitteeRole (EraCrypto era))
hotCreds <- Decoder s (Set (Credential 'HotCommitteeRole (EraCrypto era)))
forall s.
Decoder s (Set (Credential 'HotCommitteeRole (EraCrypto era)))
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 (EraCrypto 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) (CommitteeMembersState (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> BlockQuery
(ShelleyBlock proto era) (CommitteeMembersState (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall a b. (a -> b) -> a -> b
$ Set (Credential 'ColdCommitteeRole (EraCrypto era))
-> Set (Credential 'HotCommitteeRole (EraCrypto era))
-> Set MemberStatus
-> BlockQuery
(ShelleyBlock proto era) (CommitteeMembersState (EraCrypto era))
forall era proto.
ConwayEraGov era =>
Set (Credential 'ColdCommitteeRole (EraCrypto era))
-> Set (Credential 'HotCommitteeRole (EraCrypto era))
-> Set MemberStatus
-> BlockQuery
(ShelleyBlock proto era) (CommitteeMembersState (EraCrypto era))
GetCommitteeMembersState Set (Credential 'ColdCommitteeRole (EraCrypto era))
coldCreds Set (Credential 'HotCommitteeRole (EraCrypto era))
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) (VoteDelegatees (EraCrypto 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) (VoteDelegatees (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era) (VoteDelegatees (EraCrypto era)))
-> Set (Credential 'Staking (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era) (VoteDelegatees (EraCrypto era))
forall era proto.
ConwayEraGov era =>
Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era) (VoteDelegatees (EraCrypto era))
GetFilteredVoteDelegatees (Set (Credential 'Staking (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (Credential 'Staking (EraCrypto era)))
-> 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 (EraCrypto era)) 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 (EraCrypto era)) Coin)
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> (Set (KeyHash 'StakePool (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map (KeyHash 'StakePool (EraCrypto era)) Coin))
-> Set (KeyHash 'StakePool (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (KeyHash 'StakePool (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map (KeyHash 'StakePool (EraCrypto era)) Coin)
forall era proto.
ConwayEraGov era =>
Set (KeyHash 'StakePool (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map (KeyHash 'StakePool (EraCrypto era)) Coin)
GetSPOStakeDistr (Set (KeyHash 'StakePool (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (KeyHash 'StakePool (EraCrypto era)))
-> 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 (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (Seq (GovActionState era)))
-> Set (GovActionId (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set (GovActionId (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (Seq (GovActionState era))
forall era proto.
ConwayEraGov era =>
Set (GovActionId (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (Seq (GovActionState era))
GetProposals (Set (GovActionId (EraCrypto era))
-> SomeSecond BlockQuery (ShelleyBlock proto era))
-> Decoder s (Set (GovActionId (EraCrypto era)))
-> 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, 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 (ProtoCrypto proto) -> 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, Decoder Any (PParams era))
-> result -> Encoding
forall a b. (a, b) -> a
fst ((result -> Encoding, Decoder Any (PParams era))
-> result -> Encoding)
-> (result -> Encoding, Decoder Any (PParams era))
-> result
-> Encoding
forall a b. (a -> b) -> a -> b
$ ShelleyNodeToClientVersion
-> (PParams era -> Encoding, Decoder Any (PParams era))
forall era s.
(FromCBOR (PParams era), ToCBOR (PParams era),
FromCBOR (LegacyPParams era), ToCBOR (LegacyPParams era)) =>
ShelleyNodeToClientVersion
-> (PParams era -> Encoding, Decoder s (PParams era))
currentPParamsEnDecoding ShelleyNodeToClientVersion
v
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
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 (ProtoCrypto proto))
forall s. Decoder s (HeaderHash (ShelleyBlock proto era))
forall s. Decoder s (ShelleyHash (ProtoCrypto proto))
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 -> (PParams era -> Encoding, Decoder s result) -> Decoder s result
forall a b. (a, b) -> b
snd ((PParams era -> Encoding, Decoder s result) -> Decoder s result)
-> (PParams era -> Encoding, Decoder s result) -> Decoder s result
forall a b. (a -> b) -> a -> b
$ ShelleyNodeToClientVersion
-> (PParams era -> Encoding, Decoder s (PParams era))
forall era s.
(FromCBOR (PParams era), ToCBOR (PParams era),
FromCBOR (LegacyPParams era), ToCBOR (LegacyPParams era)) =>
ShelleyNodeToClientVersion
-> (PParams era -> Encoding, Decoder s (PParams era))
currentPParamsEnDecoding ShelleyNodeToClientVersion
v
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
currentPParamsEnDecoding ::
forall era s.
( FromCBOR (LC.PParams era)
, ToCBOR (LC.PParams era)
, FromCBOR (LegacyPParams era)
, ToCBOR (LegacyPParams era)
)
=> ShelleyNodeToClientVersion
-> (LC.PParams era -> Encoding, Decoder s (LC.PParams era))
currentPParamsEnDecoding :: forall era s.
(FromCBOR (PParams era), ToCBOR (PParams era),
FromCBOR (LegacyPParams era), ToCBOR (LegacyPParams era)) =>
ShelleyNodeToClientVersion
-> (PParams era -> Encoding, Decoder s (PParams era))
currentPParamsEnDecoding ShelleyNodeToClientVersion
v
| ShelleyNodeToClientVersion
v ShelleyNodeToClientVersion -> ShelleyNodeToClientVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= ShelleyNodeToClientVersion
ShelleyNodeToClientVersion7
= (PParams era -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR, Decoder s (PParams era)
forall s. Decoder s (PParams era)
forall a s. FromCBOR a => Decoder s a
fromCBOR)
| Bool
otherwise
= (PParams era -> Encoding
forall era. ToCBOR (LegacyPParams era) => PParams era -> Encoding
encodeLegacyPParams, Decoder s (PParams era)
forall era s.
FromCBOR (LegacyPParams era) =>
Decoder s (PParams era)
decodeLegacyPParams)
data StakeSnapshot crypto = StakeSnapshot
{ forall crypto. StakeSnapshot crypto -> Coin
ssMarkPool :: !SL.Coin
, forall crypto. StakeSnapshot crypto -> Coin
ssSetPool :: !SL.Coin
, forall crypto. StakeSnapshot crypto -> Coin
ssGoPool :: !SL.Coin
} deriving (StakeSnapshot crypto -> StakeSnapshot crypto -> Bool
(StakeSnapshot crypto -> StakeSnapshot crypto -> Bool)
-> (StakeSnapshot crypto -> StakeSnapshot crypto -> Bool)
-> Eq (StakeSnapshot crypto)
forall crypto. StakeSnapshot crypto -> StakeSnapshot crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall crypto. StakeSnapshot crypto -> StakeSnapshot crypto -> Bool
== :: StakeSnapshot crypto -> StakeSnapshot crypto -> Bool
$c/= :: forall crypto. StakeSnapshot crypto -> StakeSnapshot crypto -> Bool
/= :: StakeSnapshot crypto -> StakeSnapshot crypto -> Bool
Eq, Int -> StakeSnapshot crypto -> ShowS
[StakeSnapshot crypto] -> ShowS
StakeSnapshot crypto -> String
(Int -> StakeSnapshot crypto -> ShowS)
-> (StakeSnapshot crypto -> String)
-> ([StakeSnapshot crypto] -> ShowS)
-> Show (StakeSnapshot crypto)
forall crypto. Int -> StakeSnapshot crypto -> ShowS
forall crypto. [StakeSnapshot crypto] -> ShowS
forall crypto. StakeSnapshot crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall crypto. Int -> StakeSnapshot crypto -> ShowS
showsPrec :: Int -> StakeSnapshot crypto -> ShowS
$cshow :: forall crypto. StakeSnapshot crypto -> String
show :: StakeSnapshot crypto -> String
$cshowList :: forall crypto. [StakeSnapshot crypto] -> ShowS
showList :: [StakeSnapshot crypto] -> ShowS
Show, (forall x. StakeSnapshot crypto -> Rep (StakeSnapshot crypto) x)
-> (forall x. Rep (StakeSnapshot crypto) x -> StakeSnapshot crypto)
-> Generic (StakeSnapshot crypto)
forall x. Rep (StakeSnapshot crypto) x -> StakeSnapshot crypto
forall x. StakeSnapshot crypto -> Rep (StakeSnapshot crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x.
Rep (StakeSnapshot crypto) x -> StakeSnapshot crypto
forall crypto x.
StakeSnapshot crypto -> Rep (StakeSnapshot crypto) x
$cfrom :: forall crypto x.
StakeSnapshot crypto -> Rep (StakeSnapshot crypto) x
from :: forall x. StakeSnapshot crypto -> Rep (StakeSnapshot crypto) x
$cto :: forall crypto x.
Rep (StakeSnapshot crypto) x -> StakeSnapshot crypto
to :: forall x. Rep (StakeSnapshot crypto) x -> StakeSnapshot crypto
Generic)
instance NFData (StakeSnapshot crypto)
instance
Crypto crypto =>
ToCBOR (StakeSnapshot crypto)
where
toCBOR :: StakeSnapshot crypto -> Encoding
toCBOR
StakeSnapshot
{ Coin
ssMarkPool :: forall crypto. StakeSnapshot crypto -> Coin
ssMarkPool :: Coin
ssMarkPool
, Coin
ssSetPool :: forall crypto. StakeSnapshot crypto -> Coin
ssSetPool :: Coin
ssSetPool
, Coin
ssGoPool :: forall crypto. StakeSnapshot crypto -> 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
Crypto crypto =>
FromCBOR (StakeSnapshot crypto)
where
fromCBOR :: forall s. Decoder s (StakeSnapshot crypto)
fromCBOR = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"StakeSnapshot" Int
3
Coin -> Coin -> Coin -> StakeSnapshot crypto
forall crypto. Coin -> Coin -> Coin -> StakeSnapshot crypto
StakeSnapshot
(Coin -> Coin -> Coin -> StakeSnapshot crypto)
-> Decoder s Coin
-> Decoder s (Coin -> Coin -> StakeSnapshot crypto)
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 crypto)
-> Decoder s Coin -> Decoder s (Coin -> StakeSnapshot crypto)
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 crypto)
-> Decoder s Coin -> Decoder s (StakeSnapshot crypto)
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 crypto = StakeSnapshots
{ forall crypto.
StakeSnapshots crypto
-> Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
ssStakeSnapshots :: !(Map (SL.KeyHash 'SL.StakePool crypto) (StakeSnapshot crypto))
, forall crypto. StakeSnapshots crypto -> Coin
ssMarkTotal :: !SL.Coin
, forall crypto. StakeSnapshots crypto -> Coin
ssSetTotal :: !SL.Coin
, forall crypto. StakeSnapshots crypto -> Coin
ssGoTotal :: !SL.Coin
} deriving (StakeSnapshots crypto -> StakeSnapshots crypto -> Bool
(StakeSnapshots crypto -> StakeSnapshots crypto -> Bool)
-> (StakeSnapshots crypto -> StakeSnapshots crypto -> Bool)
-> Eq (StakeSnapshots crypto)
forall crypto.
StakeSnapshots crypto -> StakeSnapshots crypto -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall crypto.
StakeSnapshots crypto -> StakeSnapshots crypto -> Bool
== :: StakeSnapshots crypto -> StakeSnapshots crypto -> Bool
$c/= :: forall crypto.
StakeSnapshots crypto -> StakeSnapshots crypto -> Bool
/= :: StakeSnapshots crypto -> StakeSnapshots crypto -> Bool
Eq, Int -> StakeSnapshots crypto -> ShowS
[StakeSnapshots crypto] -> ShowS
StakeSnapshots crypto -> String
(Int -> StakeSnapshots crypto -> ShowS)
-> (StakeSnapshots crypto -> String)
-> ([StakeSnapshots crypto] -> ShowS)
-> Show (StakeSnapshots crypto)
forall crypto. Int -> StakeSnapshots crypto -> ShowS
forall crypto. [StakeSnapshots crypto] -> ShowS
forall crypto. StakeSnapshots crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall crypto. Int -> StakeSnapshots crypto -> ShowS
showsPrec :: Int -> StakeSnapshots crypto -> ShowS
$cshow :: forall crypto. StakeSnapshots crypto -> String
show :: StakeSnapshots crypto -> String
$cshowList :: forall crypto. [StakeSnapshots crypto] -> ShowS
showList :: [StakeSnapshots crypto] -> ShowS
Show, (forall x. StakeSnapshots crypto -> Rep (StakeSnapshots crypto) x)
-> (forall x.
Rep (StakeSnapshots crypto) x -> StakeSnapshots crypto)
-> Generic (StakeSnapshots crypto)
forall x. Rep (StakeSnapshots crypto) x -> StakeSnapshots crypto
forall x. StakeSnapshots crypto -> Rep (StakeSnapshots crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x.
Rep (StakeSnapshots crypto) x -> StakeSnapshots crypto
forall crypto x.
StakeSnapshots crypto -> Rep (StakeSnapshots crypto) x
$cfrom :: forall crypto x.
StakeSnapshots crypto -> Rep (StakeSnapshots crypto) x
from :: forall x. StakeSnapshots crypto -> Rep (StakeSnapshots crypto) x
$cto :: forall crypto x.
Rep (StakeSnapshots crypto) x -> StakeSnapshots crypto
to :: forall x. Rep (StakeSnapshots crypto) x -> StakeSnapshots crypto
Generic)
instance NFData (StakeSnapshots crypto)
instance
Crypto crypto =>
ToCBOR (StakeSnapshots crypto)
where
toCBOR :: StakeSnapshots crypto -> Encoding
toCBOR
StakeSnapshots
{ Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
ssStakeSnapshots :: forall crypto.
StakeSnapshots crypto
-> Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
ssStakeSnapshots :: Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
ssStakeSnapshots
, Coin
ssMarkTotal :: forall crypto. StakeSnapshots crypto -> Coin
ssMarkTotal :: Coin
ssMarkTotal
, Coin
ssSetTotal :: forall crypto. StakeSnapshots crypto -> Coin
ssSetTotal :: Coin
ssSetTotal
, Coin
ssGoTotal :: forall crypto. StakeSnapshots crypto -> Coin
ssGoTotal :: Coin
ssGoTotal
} = Word -> Encoding
encodeListLen Word
4
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto) -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
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
Crypto crypto =>
FromCBOR (StakeSnapshots crypto)
where
fromCBOR :: forall s. Decoder s (StakeSnapshots crypto)
fromCBOR = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"StakeSnapshots" Int
4
Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
-> Coin -> Coin -> Coin -> StakeSnapshots crypto
forall crypto.
Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
-> Coin -> Coin -> Coin -> StakeSnapshots crypto
StakeSnapshots
(Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto)
-> Coin -> Coin -> Coin -> StakeSnapshots crypto)
-> Decoder
s (Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto))
-> Decoder s (Coin -> Coin -> Coin -> StakeSnapshots crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto))
forall s.
Decoder s (Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto))
forall a s. FromCBOR a => Decoder s a
fromCBOR
Decoder s (Coin -> Coin -> Coin -> StakeSnapshots crypto)
-> Decoder s Coin
-> Decoder s (Coin -> Coin -> StakeSnapshots crypto)
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 crypto)
-> Decoder s Coin -> Decoder s (Coin -> StakeSnapshots crypto)
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 crypto)
-> Decoder s Coin -> Decoder s (StakeSnapshots crypto)
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