{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Cardano.Api.Internal.Query.Expr
( queryAccountState
, queryChainBlockNo
, queryChainPoint
, queryConstitution
, queryCurrentEpochState
, queryCurrentEra
, queryDebugLedgerState
, queryEpoch
, queryConstitutionHash
, queryEraHistory
, queryGenesisParameters
, queryPoolDistribution
, queryPoolState
, queryProtocolParameters
, queryProtocolState
, queryStakeAddresses
, queryStakeDelegDeposits
, queryStakeDistribution
, queryStakePoolParameters
, queryStakePools
, queryStakeSnapshot
, querySystemStart
, queryUtxo
, queryLedgerPeerSnapshot
, L.MemberStatus (..)
, L.CommitteeMembersState (..)
, queryCommitteeMembersState
, queryDRepStakeDistribution
, querySPOStakeDistribution
, queryDRepState
, queryGovState
, queryRatifyState
, queryFuturePParams
, queryStakeVoteDelegatees
, queryProposals
, queryStakePoolDefaultVote
, queryLedgerConfig
)
where
import Cardano.Api.Internal.Address
import Cardano.Api.Internal.Block
import Cardano.Api.Internal.Certificate
import Cardano.Api.Internal.Eon.BabbageEraOnwards
import Cardano.Api.Internal.Eon.Convert
import Cardano.Api.Internal.Eon.ConwayEraOnwards
import Cardano.Api.Internal.Eon.ShelleyBasedEra
import Cardano.Api.Internal.Eras
import Cardano.Api.Internal.GenesisParameters
import Cardano.Api.Internal.IPC
import Cardano.Api.Internal.IPC.Monad
import Cardano.Api.Internal.Keys.Shelley
import Cardano.Api.Internal.NetworkId
import Cardano.Api.Internal.Query
import Cardano.Api.Internal.ReexposeLedger qualified as Ledger
import Cardano.Api.Internal.Tx.UTxO
import Cardano.Ledger.Api qualified as L
import Cardano.Ledger.Api.State.Query qualified as L
import Cardano.Ledger.CertState qualified as L
import Cardano.Ledger.Coin qualified as L
import Cardano.Ledger.Credential qualified as L
import Cardano.Ledger.Hashes hiding (Hash)
import Cardano.Ledger.Keys qualified as L
import Cardano.Ledger.Shelley.LedgerState qualified as L
import Cardano.Slotting.Slot
import Ouroboros.Consensus.Cardano.Block qualified as Consensus
import Ouroboros.Consensus.HardFork.Combinator.AcrossEras as Consensus
import Ouroboros.Network.Block (Serialised)
import Ouroboros.Network.PeerSelection.LedgerPeers (LedgerPeerSnapshot)
import Data.Map (Map)
import Data.Sequence (Seq)
import Data.Set (Set)
import Data.Set qualified as S
queryChainBlockNo
:: ()
=> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (WithOrigin BlockNo))
queryChainBlockNo :: forall block point r.
LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (WithOrigin BlockNo))
queryChainBlockNo =
QueryInMode (WithOrigin BlockNo)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (WithOrigin BlockNo))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr QueryInMode (WithOrigin BlockNo)
QueryChainBlockNo
queryChainPoint
:: ()
=> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError ChainPoint)
queryChainPoint :: forall block point r.
LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError ChainPoint)
queryChainPoint =
QueryInMode ChainPoint
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError ChainPoint)
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr QueryInMode ChainPoint
QueryChainPoint
queryLedgerConfig
:: ()
=> LocalStateQueryExpr
block
point
QueryInMode
r
IO
( Either
UnsupportedNtcVersionError
(Consensus.CardanoLedgerConfig Ledger.StandardCrypto)
)
queryLedgerConfig :: forall block point r.
LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (CardanoLedgerConfig StandardCrypto))
queryLedgerConfig =
QueryInMode (CardanoLedgerConfig StandardCrypto)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (CardanoLedgerConfig StandardCrypto))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr QueryInMode (CardanoLedgerConfig StandardCrypto)
QueryLedgerConfig
queryCurrentEra
:: ()
=> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError AnyCardanoEra)
queryCurrentEra :: forall block point r.
LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError AnyCardanoEra)
queryCurrentEra =
QueryInMode AnyCardanoEra
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError AnyCardanoEra)
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr QueryInMode AnyCardanoEra
QueryCurrentEra
queryCurrentEpochState
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedCurrentEpochState era)))
queryCurrentEpochState :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedCurrentEpochState era)))
queryCurrentEpochState ShelleyBasedEra era
sbe =
QueryInMode (Either EraMismatch (SerialisedCurrentEpochState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedCurrentEpochState era)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (SerialisedCurrentEpochState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedCurrentEpochState era))))
-> QueryInMode
(Either EraMismatch (SerialisedCurrentEpochState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedCurrentEpochState era)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (SerialisedCurrentEpochState era)
-> QueryInMode
(Either EraMismatch (SerialisedCurrentEpochState era))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (SerialisedCurrentEpochState era)
-> QueryInMode
(Either EraMismatch (SerialisedCurrentEpochState era)))
-> QueryInEra era (SerialisedCurrentEpochState era)
-> QueryInMode
(Either EraMismatch (SerialisedCurrentEpochState era))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
-> QueryInEra era (SerialisedCurrentEpochState era)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
forall era.
QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
QueryCurrentEpochState
queryEpoch
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch EpochNo))
queryEpoch :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch EpochNo))
queryEpoch ShelleyBasedEra era
sbe =
QueryInMode (Either EraMismatch EpochNo)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch EpochNo))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch EpochNo)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch EpochNo)))
-> QueryInMode (Either EraMismatch EpochNo)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch EpochNo))
forall a b. (a -> b) -> a -> b
$ QueryInEra era EpochNo -> QueryInMode (Either EraMismatch EpochNo)
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era EpochNo
-> QueryInMode (Either EraMismatch EpochNo))
-> QueryInEra era EpochNo
-> QueryInMode (Either EraMismatch EpochNo)
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era EpochNo -> QueryInEra era EpochNo
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era EpochNo
forall era. QueryInShelleyBasedEra era EpochNo
QueryEpoch
queryDebugLedgerState
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedDebugLedgerState era)))
queryDebugLedgerState :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedDebugLedgerState era)))
queryDebugLedgerState ShelleyBasedEra era
sbe =
QueryInMode (Either EraMismatch (SerialisedDebugLedgerState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedDebugLedgerState era)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (SerialisedDebugLedgerState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedDebugLedgerState era))))
-> QueryInMode
(Either EraMismatch (SerialisedDebugLedgerState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedDebugLedgerState era)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (SerialisedDebugLedgerState era)
-> QueryInMode
(Either EraMismatch (SerialisedDebugLedgerState era))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (SerialisedDebugLedgerState era)
-> QueryInMode
(Either EraMismatch (SerialisedDebugLedgerState era)))
-> QueryInEra era (SerialisedDebugLedgerState era)
-> QueryInMode
(Either EraMismatch (SerialisedDebugLedgerState era))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
-> QueryInEra era (SerialisedDebugLedgerState era)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
forall era.
QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
QueryDebugLedgerState
queryLedgerPeerSnapshot
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (Serialised LedgerPeerSnapshot)))
queryLedgerPeerSnapshot :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Serialised LedgerPeerSnapshot)))
queryLedgerPeerSnapshot ShelleyBasedEra era
sbe =
QueryInMode (Either EraMismatch (Serialised LedgerPeerSnapshot))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Serialised LedgerPeerSnapshot)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (Serialised LedgerPeerSnapshot))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Serialised LedgerPeerSnapshot))))
-> QueryInMode (Either EraMismatch (Serialised LedgerPeerSnapshot))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Serialised LedgerPeerSnapshot)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Serialised LedgerPeerSnapshot)
-> QueryInMode (Either EraMismatch (Serialised LedgerPeerSnapshot))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Serialised LedgerPeerSnapshot)
-> QueryInMode
(Either EraMismatch (Serialised LedgerPeerSnapshot)))
-> QueryInEra era (Serialised LedgerPeerSnapshot)
-> QueryInMode (Either EraMismatch (Serialised LedgerPeerSnapshot))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Serialised LedgerPeerSnapshot)
-> QueryInEra era (Serialised LedgerPeerSnapshot)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (Serialised LedgerPeerSnapshot)
forall era.
QueryInShelleyBasedEra era (Serialised LedgerPeerSnapshot)
QueryLedgerPeerSnapshot
queryEraHistory
:: ()
=> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError EraHistory)
queryEraHistory :: forall block point r.
LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError EraHistory)
queryEraHistory =
QueryInMode EraHistory
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError EraHistory)
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr QueryInMode EraHistory
QueryEraHistory
queryGenesisParameters
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (GenesisParameters ShelleyEra)))
queryGenesisParameters :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (GenesisParameters ShelleyEra)))
queryGenesisParameters ShelleyBasedEra era
sbe =
QueryInMode (Either EraMismatch (GenesisParameters ShelleyEra))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (GenesisParameters ShelleyEra)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (GenesisParameters ShelleyEra))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (GenesisParameters ShelleyEra))))
-> QueryInMode (Either EraMismatch (GenesisParameters ShelleyEra))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (GenesisParameters ShelleyEra)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (GenesisParameters ShelleyEra)
-> QueryInMode (Either EraMismatch (GenesisParameters ShelleyEra))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (GenesisParameters ShelleyEra)
-> QueryInMode (Either EraMismatch (GenesisParameters ShelleyEra)))
-> QueryInEra era (GenesisParameters ShelleyEra)
-> QueryInMode (Either EraMismatch (GenesisParameters ShelleyEra))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (GenesisParameters ShelleyEra)
-> QueryInEra era (GenesisParameters ShelleyEra)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (GenesisParameters ShelleyEra)
forall era.
QueryInShelleyBasedEra era (GenesisParameters ShelleyEra)
QueryGenesisParameters
queryPoolDistribution
:: ()
=> BabbageEraOnwards era
-> Maybe (Set PoolId)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolDistribution era)))
queryPoolDistribution :: forall era block point r.
BabbageEraOnwards era
-> Maybe (Set PoolId)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedPoolDistribution era)))
queryPoolDistribution BabbageEraOnwards era
era Maybe (Set PoolId)
mPoolIds = do
let sbe :: ShelleyBasedEra era
sbe = BabbageEraOnwards era -> ShelleyBasedEra era
forall era. BabbageEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert BabbageEraOnwards era
era
QueryInMode (Either EraMismatch (SerialisedPoolDistribution era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedPoolDistribution era)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (SerialisedPoolDistribution era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedPoolDistribution era))))
-> QueryInMode
(Either EraMismatch (SerialisedPoolDistribution era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedPoolDistribution era)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (SerialisedPoolDistribution era)
-> QueryInMode
(Either EraMismatch (SerialisedPoolDistribution era))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (SerialisedPoolDistribution era)
-> QueryInMode
(Either EraMismatch (SerialisedPoolDistribution era)))
-> QueryInEra era (SerialisedPoolDistribution era)
-> QueryInMode
(Either EraMismatch (SerialisedPoolDistribution era))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
-> QueryInEra era (SerialisedPoolDistribution era)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
-> QueryInEra era (SerialisedPoolDistribution era))
-> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
-> QueryInEra era (SerialisedPoolDistribution era)
forall a b. (a -> b) -> a -> b
$ Maybe (Set PoolId)
-> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
forall era.
Maybe (Set PoolId)
-> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
QueryPoolDistribution Maybe (Set PoolId)
mPoolIds
queryPoolState
:: ()
=> BabbageEraOnwards era
-> Maybe (Set PoolId)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolState era)))
queryPoolState :: forall era block point r.
BabbageEraOnwards era
-> Maybe (Set PoolId)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedPoolState era)))
queryPoolState BabbageEraOnwards era
era Maybe (Set PoolId)
mPoolIds = do
let sbe :: ShelleyBasedEra era
sbe = BabbageEraOnwards era -> ShelleyBasedEra era
forall era. BabbageEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert BabbageEraOnwards era
era
QueryInMode (Either EraMismatch (SerialisedPoolState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedPoolState era)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (SerialisedPoolState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedPoolState era))))
-> QueryInMode (Either EraMismatch (SerialisedPoolState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedPoolState era)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (SerialisedPoolState era)
-> QueryInMode (Either EraMismatch (SerialisedPoolState era))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (SerialisedPoolState era)
-> QueryInMode (Either EraMismatch (SerialisedPoolState era)))
-> QueryInEra era (SerialisedPoolState era)
-> QueryInMode (Either EraMismatch (SerialisedPoolState era))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (SerialisedPoolState era)
-> QueryInEra era (SerialisedPoolState era)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (SerialisedPoolState era)
-> QueryInEra era (SerialisedPoolState era))
-> QueryInShelleyBasedEra era (SerialisedPoolState era)
-> QueryInEra era (SerialisedPoolState era)
forall a b. (a -> b) -> a -> b
$ Maybe (Set PoolId)
-> QueryInShelleyBasedEra era (SerialisedPoolState era)
forall era.
Maybe (Set PoolId)
-> QueryInShelleyBasedEra era (SerialisedPoolState era)
QueryPoolState Maybe (Set PoolId)
mPoolIds
queryProtocolParameters
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (Ledger.PParams (ShelleyLedgerEra era))))
queryProtocolParameters :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (PParams (ShelleyLedgerEra era))))
queryProtocolParameters ShelleyBasedEra era
sbe =
QueryInMode (Either EraMismatch (PParams (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (PParams (ShelleyLedgerEra era))))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (PParams (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (PParams (ShelleyLedgerEra era)))))
-> QueryInMode
(Either EraMismatch (PParams (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (PParams (ShelleyLedgerEra era))))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (PParams (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (PParams (ShelleyLedgerEra era)))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (PParams (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (PParams (ShelleyLedgerEra era))))
-> QueryInEra era (PParams (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (PParams (ShelleyLedgerEra era)))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era))
-> QueryInEra era (PParams (ShelleyLedgerEra era))
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era))
forall era.
QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era))
QueryProtocolParameters
queryConstitutionHash
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
( Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash L.AnchorData))
)
queryConstitutionHash :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData)))
queryConstitutionHash ShelleyBasedEra era
sbe =
((Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData)))
forall a b.
(a -> b)
-> LocalStateQueryExpr block point QueryInMode r IO a
-> LocalStateQueryExpr block point QueryInMode r IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData))))
-> ((Constitution (ShelleyLedgerEra era) -> SafeHash AnchorData)
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData)))
-> (Constitution (ShelleyLedgerEra era) -> SafeHash AnchorData)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either EraMismatch (Constitution (ShelleyLedgerEra era))
-> Either EraMismatch (SafeHash AnchorData))
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData))
forall a b.
(a -> b)
-> Either UnsupportedNtcVersionError a
-> Either UnsupportedNtcVersionError b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Either EraMismatch (Constitution (ShelleyLedgerEra era))
-> Either EraMismatch (SafeHash AnchorData))
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData)))
-> ((Constitution (ShelleyLedgerEra era) -> SafeHash AnchorData)
-> Either EraMismatch (Constitution (ShelleyLedgerEra era))
-> Either EraMismatch (SafeHash AnchorData))
-> (Constitution (ShelleyLedgerEra era) -> SafeHash AnchorData)
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Constitution (ShelleyLedgerEra era) -> SafeHash AnchorData)
-> Either EraMismatch (Constitution (ShelleyLedgerEra era))
-> Either EraMismatch (SafeHash AnchorData)
forall a b.
(a -> b) -> Either EraMismatch a -> Either EraMismatch b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) (Anchor -> SafeHash AnchorData
L.anchorDataHash (Anchor -> SafeHash AnchorData)
-> (Constitution (ShelleyLedgerEra era) -> Anchor)
-> Constitution (ShelleyLedgerEra era)
-> SafeHash AnchorData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Constitution (ShelleyLedgerEra era) -> Anchor
forall era. Constitution era -> Anchor
L.constitutionAnchor) (LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SafeHash AnchorData)))
forall a b. (a -> b) -> a -> b
$
QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))))
-> QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
forall a b. (a -> b) -> a -> b
$
QueryInEra era (Constitution (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Constitution (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
-> QueryInEra era (Constitution (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
forall a b. (a -> b) -> a -> b
$
ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
-> QueryInEra era (Constitution (ShelleyLedgerEra era))
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
forall era.
QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
QueryConstitution
queryProtocolState
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (ProtocolState era)))
queryProtocolState :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (ProtocolState era)))
queryProtocolState ShelleyBasedEra era
sbe =
QueryInMode (Either EraMismatch (ProtocolState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (ProtocolState era)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (ProtocolState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (ProtocolState era))))
-> QueryInMode (Either EraMismatch (ProtocolState era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (ProtocolState era)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (ProtocolState era)
-> QueryInMode (Either EraMismatch (ProtocolState era))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (ProtocolState era)
-> QueryInMode (Either EraMismatch (ProtocolState era)))
-> QueryInEra era (ProtocolState era)
-> QueryInMode (Either EraMismatch (ProtocolState era))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (ProtocolState era)
-> QueryInEra era (ProtocolState era)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (ProtocolState era)
forall era. QueryInShelleyBasedEra era (ProtocolState era)
QueryProtocolState
queryStakeAddresses
:: ()
=> ShelleyBasedEra era
-> Set StakeCredential
-> NetworkId
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
( Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeAddress L.Coin, Map StakeAddress PoolId))
)
queryStakeAddresses :: forall era block point r.
ShelleyBasedEra era
-> Set StakeCredential
-> NetworkId
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId)))
queryStakeAddresses ShelleyBasedEra era
sbe Set StakeCredential
stakeCredentials NetworkId
networkId =
QueryInMode
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId))))
-> QueryInMode
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
-> QueryInMode
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
-> QueryInMode
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId)))
-> QueryInEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
-> QueryInMode
(Either
EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra
era (Map StakeAddress Coin, Map StakeAddress PoolId)
-> QueryInEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra
era (Map StakeAddress Coin, Map StakeAddress PoolId)
-> QueryInEra era (Map StakeAddress Coin, Map StakeAddress PoolId))
-> QueryInShelleyBasedEra
era (Map StakeAddress Coin, Map StakeAddress PoolId)
-> QueryInEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
forall a b. (a -> b) -> a -> b
$ Set StakeCredential
-> NetworkId
-> QueryInShelleyBasedEra
era (Map StakeAddress Coin, Map StakeAddress PoolId)
forall era.
Set StakeCredential
-> NetworkId
-> QueryInShelleyBasedEra
era (Map StakeAddress Coin, Map StakeAddress PoolId)
QueryStakeAddresses Set StakeCredential
stakeCredentials NetworkId
networkId
queryStakeDelegDeposits
:: BabbageEraOnwards era
-> Set StakeCredential
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either Consensus.EraMismatch (Map StakeCredential L.Coin)))
queryStakeDelegDeposits :: forall era block point r.
BabbageEraOnwards era
-> Set StakeCredential
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin)))
queryStakeDelegDeposits BabbageEraOnwards era
era Set StakeCredential
stakeCreds
| Set StakeCredential -> Bool
forall a. Set a -> Bool
S.null Set StakeCredential
stakeCreds = Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin)))
forall a. a -> LocalStateQueryExpr block point QueryInMode r IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin))))
-> (Either EraMismatch (Map StakeCredential Coin)
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin)))
-> Either EraMismatch (Map StakeCredential Coin)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either EraMismatch (Map StakeCredential Coin)
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin))
forall a. a -> Either UnsupportedNtcVersionError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either EraMismatch (Map StakeCredential Coin)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin))))
-> Either EraMismatch (Map StakeCredential Coin)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin)))
forall a b. (a -> b) -> a -> b
$ Map StakeCredential Coin
-> Either EraMismatch (Map StakeCredential Coin)
forall a. a -> Either EraMismatch a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Map StakeCredential Coin
forall a. Monoid a => a
mempty
| Bool
otherwise = do
let sbe :: ShelleyBasedEra era
sbe = BabbageEraOnwards era -> ShelleyBasedEra era
forall era. BabbageEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert BabbageEraOnwards era
era
QueryInMode (Either EraMismatch (Map StakeCredential Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (Map StakeCredential Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin))))
-> QueryInMode (Either EraMismatch (Map StakeCredential Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential Coin)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Map StakeCredential Coin)
-> QueryInMode (Either EraMismatch (Map StakeCredential Coin))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Map StakeCredential Coin)
-> QueryInMode (Either EraMismatch (Map StakeCredential Coin)))
-> (QueryInShelleyBasedEra era (Map StakeCredential Coin)
-> QueryInEra era (Map StakeCredential Coin))
-> QueryInShelleyBasedEra era (Map StakeCredential Coin)
-> QueryInMode (Either EraMismatch (Map StakeCredential Coin))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Map StakeCredential Coin)
-> QueryInEra era (Map StakeCredential Coin)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (Map StakeCredential Coin)
-> QueryInMode (Either EraMismatch (Map StakeCredential Coin)))
-> QueryInShelleyBasedEra era (Map StakeCredential Coin)
-> QueryInMode (Either EraMismatch (Map StakeCredential Coin))
forall a b. (a -> b) -> a -> b
$ Set StakeCredential
-> QueryInShelleyBasedEra era (Map StakeCredential Coin)
forall era.
Set StakeCredential
-> QueryInShelleyBasedEra era (Map StakeCredential Coin)
QueryStakeDelegDeposits Set StakeCredential
stakeCreds
queryStakeDistribution
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (Map (Hash StakePoolKey) Rational)))
queryStakeDistribution :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId Rational)))
queryStakeDistribution ShelleyBasedEra era
sbe =
QueryInMode (Either EraMismatch (Map PoolId Rational))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId Rational)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (Map PoolId Rational))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId Rational))))
-> QueryInMode (Either EraMismatch (Map PoolId Rational))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId Rational)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Map PoolId Rational)
-> QueryInMode (Either EraMismatch (Map PoolId Rational))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Map PoolId Rational)
-> QueryInMode (Either EraMismatch (Map PoolId Rational)))
-> QueryInEra era (Map PoolId Rational)
-> QueryInMode (Either EraMismatch (Map PoolId Rational))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Map PoolId Rational)
-> QueryInEra era (Map PoolId Rational)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (Map PoolId Rational)
forall era. QueryInShelleyBasedEra era (Map PoolId Rational)
QueryStakeDistribution
queryStakePoolParameters
:: ()
=> ShelleyBasedEra era
-> Set PoolId
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (Map PoolId StakePoolParameters)))
queryStakePoolParameters :: forall era block point r.
ShelleyBasedEra era
-> Set PoolId
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters)))
queryStakePoolParameters ShelleyBasedEra era
sbe Set PoolId
poolIds
| Set PoolId -> Bool
forall a. Set a -> Bool
S.null Set PoolId
poolIds = Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters)))
forall a. a -> LocalStateQueryExpr block point QueryInMode r IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters))))
-> (Either EraMismatch (Map PoolId StakePoolParameters)
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters)))
-> Either EraMismatch (Map PoolId StakePoolParameters)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either EraMismatch (Map PoolId StakePoolParameters)
-> Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters))
forall a. a -> Either UnsupportedNtcVersionError a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either EraMismatch (Map PoolId StakePoolParameters)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters))))
-> Either EraMismatch (Map PoolId StakePoolParameters)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters)))
forall a b. (a -> b) -> a -> b
$ Map PoolId StakePoolParameters
-> Either EraMismatch (Map PoolId StakePoolParameters)
forall a. a -> Either EraMismatch a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Map PoolId StakePoolParameters
forall a. Monoid a => a
mempty
| Bool
otherwise =
QueryInMode (Either EraMismatch (Map PoolId StakePoolParameters))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (Map PoolId StakePoolParameters))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters))))
-> QueryInMode
(Either EraMismatch (Map PoolId StakePoolParameters))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map PoolId StakePoolParameters)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Map PoolId StakePoolParameters)
-> QueryInMode
(Either EraMismatch (Map PoolId StakePoolParameters))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Map PoolId StakePoolParameters)
-> QueryInMode
(Either EraMismatch (Map PoolId StakePoolParameters)))
-> QueryInEra era (Map PoolId StakePoolParameters)
-> QueryInMode
(Either EraMismatch (Map PoolId StakePoolParameters))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
-> QueryInEra era (Map PoolId StakePoolParameters)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
-> QueryInEra era (Map PoolId StakePoolParameters))
-> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
-> QueryInEra era (Map PoolId StakePoolParameters)
forall a b. (a -> b) -> a -> b
$ Set PoolId
-> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
forall era.
Set PoolId
-> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
QueryStakePoolParameters Set PoolId
poolIds
queryStakePools
:: ()
=> ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (Set PoolId)))
queryStakePools :: forall era block point r.
ShelleyBasedEra era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch (Set PoolId)))
queryStakePools ShelleyBasedEra era
sbe =
QueryInMode (Either EraMismatch (Set PoolId))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch (Set PoolId)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (Set PoolId))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch (Set PoolId))))
-> QueryInMode (Either EraMismatch (Set PoolId))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch (Set PoolId)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Set PoolId)
-> QueryInMode (Either EraMismatch (Set PoolId))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Set PoolId)
-> QueryInMode (Either EraMismatch (Set PoolId)))
-> (QueryInShelleyBasedEra era (Set PoolId)
-> QueryInEra era (Set PoolId))
-> QueryInShelleyBasedEra era (Set PoolId)
-> QueryInMode (Either EraMismatch (Set PoolId))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Set PoolId)
-> QueryInEra era (Set PoolId)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (Set PoolId)
-> QueryInMode (Either EraMismatch (Set PoolId)))
-> QueryInShelleyBasedEra era (Set PoolId)
-> QueryInMode (Either EraMismatch (Set PoolId))
forall a b. (a -> b) -> a -> b
$ QueryInShelleyBasedEra era (Set PoolId)
forall era. QueryInShelleyBasedEra era (Set PoolId)
QueryStakePools
queryStakeSnapshot
:: ()
=> BabbageEraOnwards era
-> Maybe (Set PoolId)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedStakeSnapshots era)))
queryStakeSnapshot :: forall era block point r.
BabbageEraOnwards era
-> Maybe (Set PoolId)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedStakeSnapshots era)))
queryStakeSnapshot BabbageEraOnwards era
era Maybe (Set PoolId)
mPoolIds = do
let sbe :: ShelleyBasedEra era
sbe = BabbageEraOnwards era -> ShelleyBasedEra era
forall era. BabbageEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert BabbageEraOnwards era
era
QueryInMode (Either EraMismatch (SerialisedStakeSnapshots era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedStakeSnapshots era)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (SerialisedStakeSnapshots era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedStakeSnapshots era))))
-> QueryInMode (Either EraMismatch (SerialisedStakeSnapshots era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (SerialisedStakeSnapshots era)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (SerialisedStakeSnapshots era)
-> QueryInMode (Either EraMismatch (SerialisedStakeSnapshots era))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (SerialisedStakeSnapshots era)
-> QueryInMode (Either EraMismatch (SerialisedStakeSnapshots era)))
-> QueryInEra era (SerialisedStakeSnapshots era)
-> QueryInMode (Either EraMismatch (SerialisedStakeSnapshots era))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
-> QueryInEra era (SerialisedStakeSnapshots era)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
-> QueryInEra era (SerialisedStakeSnapshots era))
-> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
-> QueryInEra era (SerialisedStakeSnapshots era)
forall a b. (a -> b) -> a -> b
$ Maybe (Set PoolId)
-> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
forall era.
Maybe (Set PoolId)
-> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
QueryStakeSnapshot Maybe (Set PoolId)
mPoolIds
querySystemStart
:: ()
=> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError SystemStart)
querySystemStart :: forall block point r.
LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError SystemStart)
querySystemStart =
QueryInMode SystemStart
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError SystemStart)
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr QueryInMode SystemStart
QuerySystemStart
queryUtxo
:: ()
=> ShelleyBasedEra era
-> QueryUTxOFilter
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (UTxO era)))
queryUtxo :: forall era block point r.
ShelleyBasedEra era
-> QueryUTxOFilter
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (UTxO era)))
queryUtxo ShelleyBasedEra era
sbe QueryUTxOFilter
utxoFilter =
QueryInMode (Either EraMismatch (UTxO era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (UTxO era)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (UTxO era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch (UTxO era))))
-> QueryInMode (Either EraMismatch (UTxO era))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (UTxO era)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (UTxO era)
-> QueryInMode (Either EraMismatch (UTxO era))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (UTxO era)
-> QueryInMode (Either EraMismatch (UTxO era)))
-> QueryInEra era (UTxO era)
-> QueryInMode (Either EraMismatch (UTxO era))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (UTxO era)
-> QueryInEra era (UTxO era)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (UTxO era)
-> QueryInEra era (UTxO era))
-> QueryInShelleyBasedEra era (UTxO era)
-> QueryInEra era (UTxO era)
forall a b. (a -> b) -> a -> b
$ QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era)
forall era.
QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era)
QueryUTxO QueryUTxOFilter
utxoFilter
queryConstitution
:: ()
=> ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (L.Constitution (ShelleyLedgerEra era))))
queryConstitution :: forall era block point r.
ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
queryConstitution ConwayEraOnwards era
era = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
era
QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))))
-> QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Constitution (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Constitution (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era))))
-> QueryInEra era (Constitution (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (Constitution (ShelleyLedgerEra era)))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
-> QueryInEra era (Constitution (ShelleyLedgerEra era))
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
forall era.
QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
QueryConstitution
queryGovState
:: ()
=> ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (L.GovState (ShelleyLedgerEra era))))
queryGovState :: forall era block point r.
ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (GovState (ShelleyLedgerEra era))))
queryGovState ConwayEraOnwards era
era = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
era
QueryInMode (Either EraMismatch (GovState (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (GovState (ShelleyLedgerEra era))))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (GovState (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (GovState (ShelleyLedgerEra era)))))
-> QueryInMode
(Either EraMismatch (GovState (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (GovState (ShelleyLedgerEra era))))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (GovState (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (GovState (ShelleyLedgerEra era)))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (GovState (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (GovState (ShelleyLedgerEra era))))
-> QueryInEra era (GovState (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (GovState (ShelleyLedgerEra era)))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era))
-> QueryInEra era (GovState (ShelleyLedgerEra era))
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era))
forall era.
QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era))
QueryGovState
queryRatifyState
:: ()
=> ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (L.RatifyState (ShelleyLedgerEra era))))
queryRatifyState :: forall era block point r.
ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (RatifyState (ShelleyLedgerEra era))))
queryRatifyState ConwayEraOnwards era
era = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
era
QueryInMode
(Either EraMismatch (RatifyState (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (RatifyState (ShelleyLedgerEra era))))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode
(Either EraMismatch (RatifyState (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (RatifyState (ShelleyLedgerEra era)))))
-> QueryInMode
(Either EraMismatch (RatifyState (ShelleyLedgerEra era)))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (RatifyState (ShelleyLedgerEra era))))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (RatifyState (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (RatifyState (ShelleyLedgerEra era)))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (RatifyState (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (RatifyState (ShelleyLedgerEra era))))
-> QueryInEra era (RatifyState (ShelleyLedgerEra era))
-> QueryInMode
(Either EraMismatch (RatifyState (ShelleyLedgerEra era)))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (RatifyState (ShelleyLedgerEra era))
-> QueryInEra era (RatifyState (ShelleyLedgerEra era))
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (RatifyState (ShelleyLedgerEra era))
forall era.
QueryInShelleyBasedEra era (RatifyState (ShelleyLedgerEra era))
QueryRatifyState
queryFuturePParams
:: ()
=> ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (Maybe (L.PParams (ShelleyLedgerEra era)))))
queryFuturePParams :: forall era block point r.
ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era)))))
queryFuturePParams ConwayEraOnwards era
era = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
era
QueryInMode
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era)))))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era))))))
-> QueryInMode
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era)))))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Maybe (PParams (ShelleyLedgerEra era)))
-> QueryInMode
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era))))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Maybe (PParams (ShelleyLedgerEra era)))
-> QueryInMode
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era)))))
-> QueryInEra era (Maybe (PParams (ShelleyLedgerEra era)))
-> QueryInMode
(Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era))))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra
era (Maybe (PParams (ShelleyLedgerEra era)))
-> QueryInEra era (Maybe (PParams (ShelleyLedgerEra era)))
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe QueryInShelleyBasedEra era (Maybe (PParams (ShelleyLedgerEra era)))
forall era.
QueryInShelleyBasedEra era (Maybe (PParams (ShelleyLedgerEra era)))
QueryFuturePParams
queryDRepState
:: ConwayEraOnwards era
-> Set (L.Credential L.DRepRole)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
( Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (L.Credential L.DRepRole) L.DRepState))
)
queryDRepState :: forall era block point r.
ConwayEraOnwards era
-> Set (Credential 'DRepRole)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (Credential 'DRepRole) DRepState)))
queryDRepState ConwayEraOnwards era
era Set (Credential 'DRepRole)
drepCreds = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
era
QueryInMode
(Either EraMismatch (Map (Credential 'DRepRole) DRepState))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (Credential 'DRepRole) DRepState)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode
(Either EraMismatch (Map (Credential 'DRepRole) DRepState))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (Credential 'DRepRole) DRepState))))
-> QueryInMode
(Either EraMismatch (Map (Credential 'DRepRole) DRepState))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (Credential 'DRepRole) DRepState)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Map (Credential 'DRepRole) DRepState)
-> QueryInMode
(Either EraMismatch (Map (Credential 'DRepRole) DRepState))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Map (Credential 'DRepRole) DRepState)
-> QueryInMode
(Either EraMismatch (Map (Credential 'DRepRole) DRepState)))
-> QueryInEra era (Map (Credential 'DRepRole) DRepState)
-> QueryInMode
(Either EraMismatch (Map (Credential 'DRepRole) DRepState))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra
era (Map (Credential 'DRepRole) DRepState)
-> QueryInEra era (Map (Credential 'DRepRole) DRepState)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (Map (Credential 'DRepRole) DRepState)
-> QueryInEra era (Map (Credential 'DRepRole) DRepState))
-> QueryInShelleyBasedEra
era (Map (Credential 'DRepRole) DRepState)
-> QueryInEra era (Map (Credential 'DRepRole) DRepState)
forall a b. (a -> b) -> a -> b
$ Set (Credential 'DRepRole)
-> QueryInShelleyBasedEra
era (Map (Credential 'DRepRole) DRepState)
forall era.
Set (Credential 'DRepRole)
-> QueryInShelleyBasedEra
era (Map (Credential 'DRepRole) DRepState)
QueryDRepState Set (Credential 'DRepRole)
drepCreds
queryDRepStakeDistribution
:: ConwayEraOnwards era
-> Set L.DRep
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch (Map L.DRep L.Coin)))
queryDRepStakeDistribution :: forall era block point r.
ConwayEraOnwards era
-> Set DRep
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch (Map DRep Coin)))
queryDRepStakeDistribution ConwayEraOnwards era
era Set DRep
dreps = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
era
QueryInMode (Either EraMismatch (Map DRep Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch (Map DRep Coin)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (Map DRep Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch (Map DRep Coin))))
-> QueryInMode (Either EraMismatch (Map DRep Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch (Map DRep Coin)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Map DRep Coin)
-> QueryInMode (Either EraMismatch (Map DRep Coin))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Map DRep Coin)
-> QueryInMode (Either EraMismatch (Map DRep Coin)))
-> QueryInEra era (Map DRep Coin)
-> QueryInMode (Either EraMismatch (Map DRep Coin))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Map DRep Coin)
-> QueryInEra era (Map DRep Coin)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (Map DRep Coin)
-> QueryInEra era (Map DRep Coin))
-> QueryInShelleyBasedEra era (Map DRep Coin)
-> QueryInEra era (Map DRep Coin)
forall a b. (a -> b) -> a -> b
$ Set DRep -> QueryInShelleyBasedEra era (Map DRep Coin)
forall era. Set DRep -> QueryInShelleyBasedEra era (Map DRep Coin)
QueryDRepStakeDistr Set DRep
dreps
querySPOStakeDistribution
:: ConwayEraOnwards era
-> Set (L.KeyHash 'L.StakePool)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
( Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (L.KeyHash 'L.StakePool) L.Coin))
)
querySPOStakeDistribution :: forall era block point r.
ConwayEraOnwards era
-> Set (KeyHash 'StakePool)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (KeyHash 'StakePool) Coin)))
querySPOStakeDistribution ConwayEraOnwards era
era Set (KeyHash 'StakePool)
spos = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
era
QueryInMode (Either EraMismatch (Map (KeyHash 'StakePool) Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (KeyHash 'StakePool) Coin)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (Map (KeyHash 'StakePool) Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (KeyHash 'StakePool) Coin))))
-> QueryInMode (Either EraMismatch (Map (KeyHash 'StakePool) Coin))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map (KeyHash 'StakePool) Coin)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Map (KeyHash 'StakePool) Coin)
-> QueryInMode (Either EraMismatch (Map (KeyHash 'StakePool) Coin))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Map (KeyHash 'StakePool) Coin)
-> QueryInMode
(Either EraMismatch (Map (KeyHash 'StakePool) Coin)))
-> QueryInEra era (Map (KeyHash 'StakePool) Coin)
-> QueryInMode (Either EraMismatch (Map (KeyHash 'StakePool) Coin))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin)
-> QueryInEra era (Map (KeyHash 'StakePool) Coin)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin)
-> QueryInEra era (Map (KeyHash 'StakePool) Coin))
-> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin)
-> QueryInEra era (Map (KeyHash 'StakePool) Coin)
forall a b. (a -> b) -> a -> b
$ Set (KeyHash 'StakePool)
-> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin)
forall era.
Set (KeyHash 'StakePool)
-> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin)
QuerySPOStakeDistr Set (KeyHash 'StakePool)
spos
queryCommitteeMembersState
:: ConwayEraOnwards era
-> Set (L.Credential L.ColdCommitteeRole)
-> Set (L.Credential L.HotCommitteeRole)
-> Set L.MemberStatus
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch L.CommitteeMembersState))
ConwayEraOnwards era
era Set (Credential 'ColdCommitteeRole)
coldCreds Set (Credential 'HotCommitteeRole)
hotCreds Set MemberStatus
statuses = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
era
QueryInMode (Either EraMismatch CommitteeMembersState)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch CommitteeMembersState))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch CommitteeMembersState)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch CommitteeMembersState)))
-> QueryInMode (Either EraMismatch CommitteeMembersState)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch CommitteeMembersState))
forall a b. (a -> b) -> a -> b
$
QueryInEra era CommitteeMembersState
-> QueryInMode (Either EraMismatch CommitteeMembersState)
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era CommitteeMembersState
-> QueryInMode (Either EraMismatch CommitteeMembersState))
-> QueryInEra era CommitteeMembersState
-> QueryInMode (Either EraMismatch CommitteeMembersState)
forall a b. (a -> b) -> a -> b
$
ShelleyBasedEra era
-> QueryInShelleyBasedEra era CommitteeMembersState
-> QueryInEra era CommitteeMembersState
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (Set (Credential 'ColdCommitteeRole)
-> Set (Credential 'HotCommitteeRole)
-> Set MemberStatus
-> QueryInShelleyBasedEra era CommitteeMembersState
forall era.
Set (Credential 'ColdCommitteeRole)
-> Set (Credential 'HotCommitteeRole)
-> Set MemberStatus
-> QueryInShelleyBasedEra era CommitteeMembersState
QueryCommitteeMembersState Set (Credential 'ColdCommitteeRole)
coldCreds Set (Credential 'HotCommitteeRole)
hotCreds Set MemberStatus
statuses)
queryStakeVoteDelegatees
:: ConwayEraOnwards era
-> Set StakeCredential
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
( Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential L.DRep))
)
queryStakeVoteDelegatees :: forall era block point r.
ConwayEraOnwards era
-> Set StakeCredential
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential DRep)))
queryStakeVoteDelegatees ConwayEraOnwards era
era Set StakeCredential
stakeCredentials = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
era
QueryInMode (Either EraMismatch (Map StakeCredential DRep))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential DRep)))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch (Map StakeCredential DRep))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential DRep))))
-> QueryInMode (Either EraMismatch (Map StakeCredential DRep))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Map StakeCredential DRep)))
forall a b. (a -> b) -> a -> b
$ QueryInEra era (Map StakeCredential DRep)
-> QueryInMode (Either EraMismatch (Map StakeCredential DRep))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Map StakeCredential DRep)
-> QueryInMode (Either EraMismatch (Map StakeCredential DRep)))
-> QueryInEra era (Map StakeCredential DRep)
-> QueryInMode (Either EraMismatch (Map StakeCredential DRep))
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era
-> QueryInShelleyBasedEra era (Map StakeCredential DRep)
-> QueryInEra era (Map StakeCredential DRep)
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era (Map StakeCredential DRep)
-> QueryInEra era (Map StakeCredential DRep))
-> QueryInShelleyBasedEra era (Map StakeCredential DRep)
-> QueryInEra era (Map StakeCredential DRep)
forall a b. (a -> b) -> a -> b
$ Set StakeCredential
-> QueryInShelleyBasedEra era (Map StakeCredential DRep)
forall era.
Set StakeCredential
-> QueryInShelleyBasedEra era (Map StakeCredential DRep)
QueryStakeVoteDelegatees Set StakeCredential
stakeCredentials
queryAccountState
:: ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either UnsupportedNtcVersionError (Either EraMismatch L.AccountState))
queryAccountState :: forall era block point r.
ConwayEraOnwards era
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch AccountState))
queryAccountState ConwayEraOnwards era
cOnwards =
QueryInMode (Either EraMismatch AccountState)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch AccountState))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch AccountState)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch AccountState)))
-> QueryInMode (Either EraMismatch AccountState)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch AccountState))
forall a b. (a -> b) -> a -> b
$
QueryInEra era AccountState
-> QueryInMode (Either EraMismatch AccountState)
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era AccountState
-> QueryInMode (Either EraMismatch AccountState))
-> (QueryInShelleyBasedEra era AccountState
-> QueryInEra era AccountState)
-> QueryInShelleyBasedEra era AccountState
-> QueryInMode (Either EraMismatch AccountState)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShelleyBasedEra era
-> QueryInShelleyBasedEra era AccountState
-> QueryInEra era AccountState
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra (ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
cOnwards) (QueryInShelleyBasedEra era AccountState
-> QueryInMode (Either EraMismatch AccountState))
-> QueryInShelleyBasedEra era AccountState
-> QueryInMode (Either EraMismatch AccountState)
forall a b. (a -> b) -> a -> b
$
QueryInShelleyBasedEra era AccountState
forall era. QueryInShelleyBasedEra era AccountState
QueryAccountState
queryProposals
:: forall era block point r
. ConwayEraOnwards era
-> Set L.GovActionId
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
( Either
UnsupportedNtcVersionError
(Either EraMismatch (Seq (L.GovActionState (ShelleyLedgerEra era))))
)
queryProposals :: forall era block point r.
ConwayEraOnwards era
-> Set GovActionId
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era)))))
queryProposals ConwayEraOnwards era
cOnwards Set GovActionId
govActionIds = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
cOnwards
QueryInMode
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era)))))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either
EraMismatch (Seq (GovActionState (ShelleyLedgerEra era))))))
-> QueryInMode
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era))))
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era)))))
forall a b. (a -> b) -> a -> b
$
QueryInEra era (Seq (GovActionState (ShelleyLedgerEra era)))
-> QueryInMode
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era))))
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era (Seq (GovActionState (ShelleyLedgerEra era)))
-> QueryInMode
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era)))))
-> (QueryInShelleyBasedEra
era (Seq (GovActionState (ShelleyLedgerEra era)))
-> QueryInEra era (Seq (GovActionState (ShelleyLedgerEra era))))
-> QueryInShelleyBasedEra
era (Seq (GovActionState (ShelleyLedgerEra era)))
-> QueryInMode
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era))))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShelleyBasedEra era
-> QueryInShelleyBasedEra
era (Seq (GovActionState (ShelleyLedgerEra era)))
-> QueryInEra era (Seq (GovActionState (ShelleyLedgerEra era)))
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra
era (Seq (GovActionState (ShelleyLedgerEra era)))
-> QueryInMode
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era)))))
-> QueryInShelleyBasedEra
era (Seq (GovActionState (ShelleyLedgerEra era)))
-> QueryInMode
(Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era))))
forall a b. (a -> b) -> a -> b
$
Set GovActionId
-> QueryInShelleyBasedEra
era (Seq (GovActionState (ShelleyLedgerEra era)))
forall era.
Set GovActionId
-> QueryInShelleyBasedEra
era (Seq (GovActionState (ShelleyLedgerEra era)))
QueryProposals Set GovActionId
govActionIds
queryStakePoolDefaultVote
:: forall era block point r
. ConwayEraOnwards era
-> L.KeyHash 'L.StakePool
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
( Either
UnsupportedNtcVersionError
(Either EraMismatch L.DefaultVote)
)
queryStakePoolDefaultVote :: forall era block point r.
ConwayEraOnwards era
-> KeyHash 'StakePool
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch DefaultVote))
queryStakePoolDefaultVote ConwayEraOnwards era
cOnwards KeyHash 'StakePool
stakePools = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
forall a (f :: a -> *) (g :: a -> *) (era :: a).
Convert f g =>
f era -> g era
convert ConwayEraOnwards era
cOnwards
QueryInMode (Either EraMismatch DefaultVote)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch DefaultVote))
forall a block point r.
QueryInMode a
-> LocalStateQueryExpr
block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
queryExpr (QueryInMode (Either EraMismatch DefaultVote)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch DefaultVote)))
-> QueryInMode (Either EraMismatch DefaultVote)
-> LocalStateQueryExpr
block
point
QueryInMode
r
IO
(Either
UnsupportedNtcVersionError (Either EraMismatch DefaultVote))
forall a b. (a -> b) -> a -> b
$
QueryInEra era DefaultVote
-> QueryInMode (Either EraMismatch DefaultVote)
forall era result1.
QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
QueryInEra (QueryInEra era DefaultVote
-> QueryInMode (Either EraMismatch DefaultVote))
-> (QueryInShelleyBasedEra era DefaultVote
-> QueryInEra era DefaultVote)
-> QueryInShelleyBasedEra era DefaultVote
-> QueryInMode (Either EraMismatch DefaultVote)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShelleyBasedEra era
-> QueryInShelleyBasedEra era DefaultVote
-> QueryInEra era DefaultVote
forall era result.
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result -> QueryInEra era result
QueryInShelleyBasedEra ShelleyBasedEra era
sbe (QueryInShelleyBasedEra era DefaultVote
-> QueryInMode (Either EraMismatch DefaultVote))
-> QueryInShelleyBasedEra era DefaultVote
-> QueryInMode (Either EraMismatch DefaultVote)
forall a b. (a -> b) -> a -> b
$
KeyHash 'StakePool -> QueryInShelleyBasedEra era DefaultVote
forall era.
KeyHash 'StakePool -> QueryInShelleyBasedEra era DefaultVote
QueryStakePoolDefaultVote KeyHash 'StakePool
stakePools