{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
module Cardano.Api.Query (
QueryInMode(..),
QueryInEra(..),
QueryInShelleyBasedEra(..),
QueryUTxOFilter(..),
UTxO(..),
UTxOInAnyEra(..),
toConsensusQuery,
fromConsensusQueryResult,
SerialisedDebugLedgerState(..),
ProtocolState(..),
decodeProtocolState,
DebugLedgerState(..),
decodeDebugLedgerState,
SerialisedCurrentEpochState(..),
CurrentEpochState(..),
decodeCurrentEpochState,
EraHistory(..),
SystemStart(..),
SlotsInEpoch(..),
SlotsToEpochEnd(..),
slotToEpoch,
LedgerState(..),
getProgress,
toLedgerUTxO,
fromLedgerUTxO,
) where
import Control.Monad (forM)
import Data.Aeson (FromJSON (..), ToJSON (..), object, withObject, (.=))
import qualified Data.Aeson as Aeson
import Data.Aeson.Types (Parser)
import Data.Bifunctor (bimap, first)
import qualified Data.ByteString.Lazy as LBS
import qualified Data.HashMap.Strict as HMS
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe (mapMaybe)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Sharing (FromSharedCBOR, Interns, Share)
import Data.SOP.Strict (SListI)
import Data.Text (Text)
import Data.Typeable
import Prelude
import Ouroboros.Network.Protocol.LocalStateQuery.Client (Some (..))
import qualified Ouroboros.Consensus.HardFork.Combinator as Consensus
import Ouroboros.Consensus.HardFork.Combinator.AcrossEras (EraMismatch)
import qualified Ouroboros.Consensus.HardFork.Combinator.AcrossEras as Consensus
import qualified Ouroboros.Consensus.HardFork.Combinator.Degenerate as Consensus
import qualified Ouroboros.Consensus.HardFork.History as History
import qualified Ouroboros.Consensus.HardFork.History.Qry as Qry
import Ouroboros.Consensus.BlockchainTime.WallClock.Types (RelativeTime, SlotLength)
import qualified Ouroboros.Consensus.Byron.Ledger as Consensus
import Ouroboros.Consensus.Cardano.Block (LedgerState (..), StandardCrypto)
import qualified Ouroboros.Consensus.Cardano.Block as Consensus
import qualified Ouroboros.Consensus.Ledger.Query as Consensus
import qualified Ouroboros.Consensus.Protocol.Abstract as Consensus
import qualified Ouroboros.Consensus.Shelley.Ledger as Consensus
import Ouroboros.Network.Block (Serialised (..))
import Cardano.Binary
import Cardano.Slotting.Slot (WithOrigin (..))
import Cardano.Slotting.Time (SystemStart (..))
import qualified Cardano.Chain.Update.Validation.Interface as Byron.Update
import qualified Cardano.Ledger.Core as Core
import qualified Cardano.Ledger.Era as Ledger
import qualified Control.State.Transition.Extended as Ledger
import qualified Cardano.Ledger.Shelley.API as Shelley
import qualified Cardano.Ledger.Shelley.LedgerState as Shelley
import Cardano.Api.Address
import Cardano.Api.Block
import Cardano.Api.Certificate
import Cardano.Api.EraCast
import Cardano.Api.Eras
import Cardano.Api.GenesisParameters
import Cardano.Api.KeysShelley
import Cardano.Api.Modes
import Cardano.Api.NetworkId
import Cardano.Api.Orphans ()
import Cardano.Api.ProtocolParameters
import Cardano.Api.TxBody
import Cardano.Api.Value
import Data.Word (Word64)
import qualified Data.Aeson.KeyMap as KeyMap
data QueryInMode mode result where
QueryCurrentEra
:: ConsensusModeIsMultiEra mode
-> QueryInMode mode AnyCardanoEra
QueryInEra
:: EraInMode era mode
-> QueryInEra era result
-> QueryInMode mode (Either EraMismatch result)
QueryEraHistory
:: ConsensusModeIsMultiEra mode
-> QueryInMode mode (EraHistory mode)
QuerySystemStart
:: QueryInMode mode SystemStart
QueryChainBlockNo
:: QueryInMode mode (WithOrigin BlockNo)
QueryChainPoint
:: ConsensusMode mode
-> QueryInMode mode ChainPoint
data EraHistory mode where
EraHistory
:: ConsensusBlockForMode mode ~ Consensus.HardForkBlock xs
=> ConsensusMode mode
-> History.Interpreter xs
-> EraHistory mode
getProgress :: SlotNo -> EraHistory mode -> Either Qry.PastHorizonException (RelativeTime, SlotLength)
getProgress :: SlotNo
-> EraHistory mode
-> Either PastHorizonException (RelativeTime, SlotLength)
getProgress SlotNo
slotNo (EraHistory ConsensusMode mode
_ Interpreter xs
interpreter) = Interpreter xs
-> Qry (RelativeTime, SlotLength)
-> Either PastHorizonException (RelativeTime, SlotLength)
forall (xs :: [*]) a.
HasCallStack =>
Interpreter xs -> Qry a -> Either PastHorizonException a
Qry.interpretQuery Interpreter xs
interpreter (SlotNo -> Qry (RelativeTime, SlotLength)
Qry.slotToWallclock SlotNo
slotNo)
newtype SlotsInEpoch = SlotsInEpoch Word64
newtype SlotsToEpochEnd = SlotsToEpochEnd Word64
slotToEpoch :: SlotNo -> EraHistory mode -> Either Qry.PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
slotToEpoch :: SlotNo
-> EraHistory mode
-> Either
PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
slotToEpoch SlotNo
slotNo (EraHistory ConsensusMode mode
_ Interpreter xs
interpreter) = case Interpreter xs
-> Qry (EpochNo, Word64, Word64)
-> Either PastHorizonException (EpochNo, Word64, Word64)
forall (xs :: [*]) a.
HasCallStack =>
Interpreter xs -> Qry a -> Either PastHorizonException a
Qry.interpretQuery Interpreter xs
interpreter (SlotNo -> Qry (EpochNo, Word64, Word64)
Qry.slotToEpoch SlotNo
slotNo) of
Right (EpochNo
epochNumber, Word64
slotsInEpoch, Word64
slotsToEpochEnd) -> (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
-> Either
PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
forall a b. b -> Either a b
Right (EpochNo
epochNumber, Word64 -> SlotsInEpoch
SlotsInEpoch Word64
slotsInEpoch, Word64 -> SlotsToEpochEnd
SlotsToEpochEnd Word64
slotsToEpochEnd)
Left PastHorizonException
e -> PastHorizonException
-> Either
PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
forall a b. a -> Either a b
Left PastHorizonException
e
deriving instance Show (QueryInMode mode result)
data QueryInEra era result where
QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState
QueryInShelleyBasedEra :: ShelleyBasedEra era
-> QueryInShelleyBasedEra era result
-> QueryInEra era result
deriving instance Show (QueryInEra era result)
data QueryInShelleyBasedEra era result where
QueryEpoch
:: QueryInShelleyBasedEra era EpochNo
QueryGenesisParameters
:: QueryInShelleyBasedEra era GenesisParameters
QueryProtocolParameters
:: QueryInShelleyBasedEra era ProtocolParameters
QueryProtocolParametersUpdate
:: QueryInShelleyBasedEra era
(Map (Hash GenesisKey) ProtocolParametersUpdate)
QueryStakeDistribution
:: QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational)
QueryUTxO
:: QueryUTxOFilter
-> QueryInShelleyBasedEra era (UTxO era)
QueryStakeAddresses
:: Set StakeCredential
-> NetworkId
-> QueryInShelleyBasedEra era (Map StakeAddress Lovelace,
Map StakeAddress PoolId)
QueryStakePools
:: QueryInShelleyBasedEra era (Set PoolId)
QueryStakePoolParameters
:: Set PoolId
-> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
QueryDebugLedgerState
:: QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
QueryProtocolState
:: QueryInShelleyBasedEra era (ProtocolState era)
QueryCurrentEpochState
:: QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
deriving instance Show (QueryInShelleyBasedEra era result)
data QueryUTxOFilter =
QueryUTxOWhole
| QueryUTxOByAddress (Set AddressAny)
| QueryUTxOByTxIn (Set TxIn)
deriving (QueryUTxOFilter -> QueryUTxOFilter -> Bool
(QueryUTxOFilter -> QueryUTxOFilter -> Bool)
-> (QueryUTxOFilter -> QueryUTxOFilter -> Bool)
-> Eq QueryUTxOFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryUTxOFilter -> QueryUTxOFilter -> Bool
$c/= :: QueryUTxOFilter -> QueryUTxOFilter -> Bool
== :: QueryUTxOFilter -> QueryUTxOFilter -> Bool
$c== :: QueryUTxOFilter -> QueryUTxOFilter -> Bool
Eq, Int -> QueryUTxOFilter -> ShowS
[QueryUTxOFilter] -> ShowS
QueryUTxOFilter -> String
(Int -> QueryUTxOFilter -> ShowS)
-> (QueryUTxOFilter -> String)
-> ([QueryUTxOFilter] -> ShowS)
-> Show QueryUTxOFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryUTxOFilter] -> ShowS
$cshowList :: [QueryUTxOFilter] -> ShowS
show :: QueryUTxOFilter -> String
$cshow :: QueryUTxOFilter -> String
showsPrec :: Int -> QueryUTxOFilter -> ShowS
$cshowsPrec :: Int -> QueryUTxOFilter -> ShowS
Show)
newtype ByronUpdateState = ByronUpdateState Byron.Update.State
deriving Int -> ByronUpdateState -> ShowS
[ByronUpdateState] -> ShowS
ByronUpdateState -> String
(Int -> ByronUpdateState -> ShowS)
-> (ByronUpdateState -> String)
-> ([ByronUpdateState] -> ShowS)
-> Show ByronUpdateState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ByronUpdateState] -> ShowS
$cshowList :: [ByronUpdateState] -> ShowS
show :: ByronUpdateState -> String
$cshow :: ByronUpdateState -> String
showsPrec :: Int -> ByronUpdateState -> ShowS
$cshowsPrec :: Int -> ByronUpdateState -> ShowS
Show
newtype UTxO era = UTxO { UTxO era -> Map TxIn (TxOut CtxUTxO era)
unUTxO :: Map TxIn (TxOut CtxUTxO era) }
deriving (UTxO era -> UTxO era -> Bool
(UTxO era -> UTxO era -> Bool)
-> (UTxO era -> UTxO era -> Bool) -> Eq (UTxO era)
forall era. UTxO era -> UTxO era -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UTxO era -> UTxO era -> Bool
$c/= :: forall era. UTxO era -> UTxO era -> Bool
== :: UTxO era -> UTxO era -> Bool
$c== :: forall era. UTxO era -> UTxO era -> Bool
Eq, Int -> UTxO era -> ShowS
[UTxO era] -> ShowS
UTxO era -> String
(Int -> UTxO era -> ShowS)
-> (UTxO era -> String) -> ([UTxO era] -> ShowS) -> Show (UTxO era)
forall era. Int -> UTxO era -> ShowS
forall era. [UTxO era] -> ShowS
forall era. UTxO era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UTxO era] -> ShowS
$cshowList :: forall era. [UTxO era] -> ShowS
show :: UTxO era -> String
$cshow :: forall era. UTxO era -> String
showsPrec :: Int -> UTxO era -> ShowS
$cshowsPrec :: forall era. Int -> UTxO era -> ShowS
Show)
instance EraCast UTxO where
eraCast :: CardanoEra toEra
-> UTxO fromEra -> Either EraCastError (UTxO toEra)
eraCast CardanoEra toEra
toEra' (UTxO Map TxIn (TxOut CtxUTxO fromEra)
m) = Map TxIn (TxOut CtxUTxO toEra) -> UTxO toEra
forall era. Map TxIn (TxOut CtxUTxO era) -> UTxO era
UTxO (Map TxIn (TxOut CtxUTxO toEra) -> UTxO toEra)
-> Either EraCastError (Map TxIn (TxOut CtxUTxO toEra))
-> Either EraCastError (UTxO toEra)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map TxIn (TxOut CtxUTxO fromEra)
-> (TxOut CtxUTxO fromEra
-> Either EraCastError (TxOut CtxUTxO toEra))
-> Either EraCastError (Map TxIn (TxOut CtxUTxO toEra))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM Map TxIn (TxOut CtxUTxO fromEra)
m (CardanoEra toEra
-> TxOut CtxUTxO fromEra
-> Either EraCastError (TxOut CtxUTxO toEra)
forall (f :: * -> *) fromEra toEra.
(EraCast f, IsCardanoEra fromEra, IsCardanoEra toEra) =>
CardanoEra toEra -> f fromEra -> Either EraCastError (f toEra)
eraCast CardanoEra toEra
toEra')
data UTxOInAnyEra where
UTxOInAnyEra :: CardanoEra era
-> UTxO era
-> UTxOInAnyEra
deriving instance Show UTxOInAnyEra
instance IsCardanoEra era => ToJSON (UTxO era) where
toJSON :: UTxO era -> Value
toJSON (UTxO Map TxIn (TxOut CtxUTxO era)
m) = Map TxIn (TxOut CtxUTxO era) -> Value
forall a. ToJSON a => a -> Value
toJSON Map TxIn (TxOut CtxUTxO era)
m
toEncoding :: UTxO era -> Encoding
toEncoding (UTxO Map TxIn (TxOut CtxUTxO era)
m) = Map TxIn (TxOut CtxUTxO era) -> Encoding
forall a. ToJSON a => a -> Encoding
toEncoding Map TxIn (TxOut CtxUTxO era)
m
instance (IsCardanoEra era, IsShelleyBasedEra era, FromJSON (TxOut CtxUTxO era))
=> FromJSON (UTxO era) where
parseJSON :: Value -> Parser (UTxO era)
parseJSON = String
-> (Object -> Parser (UTxO era)) -> Value -> Parser (UTxO era)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UTxO" ((Object -> Parser (UTxO era)) -> Value -> Parser (UTxO era))
-> (Object -> Parser (UTxO era)) -> Value -> Parser (UTxO era)
forall a b. (a -> b) -> a -> b
$ \Object
hm -> do
let l :: [(Text, Value)]
l = HashMap Text Value -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
HMS.toList (HashMap Text Value -> [(Text, Value)])
-> HashMap Text Value -> [(Text, Value)]
forall a b. (a -> b) -> a -> b
$ Object -> HashMap Text Value
forall v. KeyMap v -> HashMap Text v
KeyMap.toHashMapText Object
hm
[(TxIn, TxOut CtxUTxO era)]
res <- ((Text, Value) -> Parser (TxIn, TxOut CtxUTxO era))
-> [(Text, Value)] -> Parser [(TxIn, TxOut CtxUTxO era)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (Text, Value) -> Parser (TxIn, TxOut CtxUTxO era)
toTxIn [(Text, Value)]
l
UTxO era -> Parser (UTxO era)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (UTxO era -> Parser (UTxO era))
-> (Map TxIn (TxOut CtxUTxO era) -> UTxO era)
-> Map TxIn (TxOut CtxUTxO era)
-> Parser (UTxO era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map TxIn (TxOut CtxUTxO era) -> UTxO era
forall era. Map TxIn (TxOut CtxUTxO era) -> UTxO era
UTxO (Map TxIn (TxOut CtxUTxO era) -> Parser (UTxO era))
-> Map TxIn (TxOut CtxUTxO era) -> Parser (UTxO era)
forall a b. (a -> b) -> a -> b
$ [(TxIn, TxOut CtxUTxO era)] -> Map TxIn (TxOut CtxUTxO era)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(TxIn, TxOut CtxUTxO era)]
res
where
toTxIn :: (Text, Aeson.Value) -> Parser (TxIn, TxOut CtxUTxO era)
toTxIn :: (Text, Value) -> Parser (TxIn, TxOut CtxUTxO era)
toTxIn (Text
txinText, Value
txOutVal) = do
(,) (TxIn -> TxOut CtxUTxO era -> (TxIn, TxOut CtxUTxO era))
-> Parser TxIn
-> Parser (TxOut CtxUTxO era -> (TxIn, TxOut CtxUTxO era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser TxIn
forall a. FromJSON a => Value -> Parser a
parseJSON (Text -> Value
Aeson.String Text
txinText)
Parser (TxOut CtxUTxO era -> (TxIn, TxOut CtxUTxO era))
-> Parser (TxOut CtxUTxO era) -> Parser (TxIn, TxOut CtxUTxO era)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> Parser (TxOut CtxUTxO era)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
txOutVal
newtype SerialisedDebugLedgerState era
= SerialisedDebugLedgerState (Serialised (Shelley.NewEpochState (ShelleyLedgerEra era)))
decodeDebugLedgerState :: forall era. ()
=> FromCBOR (DebugLedgerState era)
=> SerialisedDebugLedgerState era
-> Either LBS.ByteString (DebugLedgerState era)
decodeDebugLedgerState :: SerialisedDebugLedgerState era
-> Either ByteString (DebugLedgerState era)
decodeDebugLedgerState (SerialisedDebugLedgerState (Serialised ByteString
ls)) =
(DecoderError -> ByteString)
-> Either DecoderError (DebugLedgerState era)
-> Either ByteString (DebugLedgerState era)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (ByteString -> DecoderError -> ByteString
forall a b. a -> b -> a
const ByteString
ls) (ByteString -> Either DecoderError (DebugLedgerState era)
forall a. FromCBOR a => ByteString -> Either DecoderError a
decodeFull ByteString
ls)
data DebugLedgerState era where
DebugLedgerState :: ShelleyLedgerEra era ~ ledgerera => Shelley.NewEpochState ledgerera -> DebugLedgerState era
instance
( Typeable era
, Ledger.Era (ShelleyLedgerEra era)
, FromCBOR (Core.PParams (ShelleyLedgerEra era))
, FromCBOR (Shelley.StashedAVVMAddresses (ShelleyLedgerEra era))
, FromCBOR (Core.Value (ShelleyLedgerEra era))
, FromCBOR (Ledger.State (Core.EraRule "PPUP" (ShelleyLedgerEra era)))
, Share (Core.TxOut (ShelleyLedgerEra era)) ~ Interns (Shelley.Credential 'Shelley.Staking (Ledger.Crypto (ShelleyLedgerEra era)))
, FromSharedCBOR (Core.TxOut (ShelleyLedgerEra era))
) => FromCBOR (DebugLedgerState era) where
fromCBOR :: Decoder s (DebugLedgerState era)
fromCBOR = NewEpochState (ShelleyLedgerEra era) -> DebugLedgerState era
forall era ledgerera.
(ShelleyLedgerEra era ~ ledgerera) =>
NewEpochState ledgerera -> DebugLedgerState era
DebugLedgerState (NewEpochState (ShelleyLedgerEra era) -> DebugLedgerState era)
-> Decoder s (NewEpochState (ShelleyLedgerEra era))
-> Decoder s (DebugLedgerState era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall s. Decoder s (NewEpochState (ShelleyLedgerEra era))
forall a s. FromCBOR a => Decoder s a
fromCBOR :: Decoder s (Shelley.NewEpochState (ShelleyLedgerEra era)))
instance ( IsShelleyBasedEra era
, ShelleyLedgerEra era ~ ledgerera
, Consensus.ShelleyBasedEra ledgerera
, ToJSON (Core.PParams ledgerera)
, ToJSON (Core.PParamsDelta ledgerera)
, ToJSON (Core.TxOut ledgerera)
, Share (Core.TxOut (ShelleyLedgerEra era)) ~ Interns (Shelley.Credential 'Shelley.Staking (Ledger.Crypto (ShelleyLedgerEra era)))
) => ToJSON (DebugLedgerState era) where
toJSON :: DebugLedgerState era -> Value
toJSON = [Pair] -> Value
object ([Pair] -> Value)
-> (DebugLedgerState era -> [Pair])
-> DebugLedgerState era
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DebugLedgerState era -> [Pair]
forall era ledgerera a.
(ShelleyLedgerEra era ~ ledgerera, ShelleyBasedEra ledgerera,
ToJSON (PParams ledgerera), ToJSON (PParamsDelta ledgerera),
ToJSON (TxOut ledgerera), KeyValue a) =>
DebugLedgerState era -> [a]
toDebugLedgerStatePair
toEncoding :: DebugLedgerState era -> Encoding
toEncoding = Series -> Encoding
Aeson.pairs (Series -> Encoding)
-> (DebugLedgerState era -> Series)
-> DebugLedgerState era
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat ([Series] -> Series)
-> (DebugLedgerState era -> [Series])
-> DebugLedgerState era
-> Series
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DebugLedgerState era -> [Series]
forall era ledgerera a.
(ShelleyLedgerEra era ~ ledgerera, ShelleyBasedEra ledgerera,
ToJSON (PParams ledgerera), ToJSON (PParamsDelta ledgerera),
ToJSON (TxOut ledgerera), KeyValue a) =>
DebugLedgerState era -> [a]
toDebugLedgerStatePair
toDebugLedgerStatePair ::
( ShelleyLedgerEra era ~ ledgerera
, Consensus.ShelleyBasedEra ledgerera
, ToJSON (Core.PParams ledgerera)
, ToJSON (Core.PParamsDelta ledgerera)
, ToJSON (Core.TxOut ledgerera)
, Aeson.KeyValue a
) => DebugLedgerState era -> [a]
toDebugLedgerStatePair :: DebugLedgerState era -> [a]
toDebugLedgerStatePair (DebugLedgerState NewEpochState ledgerera
newEpochS) =
let !nesEL :: EpochNo
nesEL = NewEpochState ledgerera -> EpochNo
forall era. NewEpochState era -> EpochNo
Shelley.nesEL NewEpochState ledgerera
newEpochS
!nesBprev :: BlocksMade (Crypto ledgerera)
nesBprev = NewEpochState ledgerera -> BlocksMade (Crypto ledgerera)
forall era. NewEpochState era -> BlocksMade (Crypto era)
Shelley.nesBprev NewEpochState ledgerera
newEpochS
!nesBcur :: BlocksMade (Crypto ledgerera)
nesBcur = NewEpochState ledgerera -> BlocksMade (Crypto ledgerera)
forall era. NewEpochState era -> BlocksMade (Crypto era)
Shelley.nesBcur NewEpochState ledgerera
newEpochS
!nesEs :: EpochState ledgerera
nesEs = NewEpochState ledgerera -> EpochState ledgerera
forall era. NewEpochState era -> EpochState era
Shelley.nesEs NewEpochState ledgerera
newEpochS
!nesRu :: StrictMaybe (PulsingRewUpdate (Crypto ledgerera))
nesRu = NewEpochState ledgerera
-> StrictMaybe (PulsingRewUpdate (Crypto ledgerera))
forall era.
NewEpochState era -> StrictMaybe (PulsingRewUpdate (Crypto era))
Shelley.nesRu NewEpochState ledgerera
newEpochS
!nesPd :: PoolDistr (Crypto ledgerera)
nesPd = NewEpochState ledgerera -> PoolDistr (Crypto ledgerera)
forall era. NewEpochState era -> PoolDistr (Crypto era)
Shelley.nesPd NewEpochState ledgerera
newEpochS
in [ Key
"lastEpoch" Key -> EpochNo -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= EpochNo
nesEL
, Key
"blocksBefore" Key -> BlocksMade (Crypto ledgerera) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= BlocksMade (Crypto ledgerera)
BlocksMade (Crypto ledgerera)
nesBprev
, Key
"blocksCurrent" Key -> BlocksMade (Crypto ledgerera) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= BlocksMade (Crypto ledgerera)
BlocksMade (Crypto ledgerera)
nesBcur
, Key
"stateBefore" Key -> EpochState ledgerera -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= EpochState ledgerera
nesEs
, Key
"possibleRewardUpdate" Key -> StrictMaybe (PulsingRewUpdate (Crypto ledgerera)) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe (PulsingRewUpdate (Crypto ledgerera))
StrictMaybe (PulsingRewUpdate (Crypto ledgerera))
nesRu
, Key
"stakeDistrib" Key -> PoolDistr (Crypto ledgerera) -> a
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= PoolDistr (Crypto ledgerera)
PoolDistr (Crypto ledgerera)
nesPd
]
newtype ProtocolState era
= ProtocolState (Serialised (Consensus.ChainDepState (ConsensusProtocol era)))
decodeProtocolState
:: FromCBOR (Consensus.ChainDepState (ConsensusProtocol era))
=> ProtocolState era
-> Either (LBS.ByteString, DecoderError) (Consensus.ChainDepState (ConsensusProtocol era))
decodeProtocolState :: ProtocolState era
-> Either
(ByteString, DecoderError) (ChainDepState (ConsensusProtocol era))
decodeProtocolState (ProtocolState (Serialised ByteString
pbs)) = (DecoderError -> (ByteString, DecoderError))
-> Either DecoderError (ChainDepState (ConsensusProtocol era))
-> Either
(ByteString, DecoderError) (ChainDepState (ConsensusProtocol era))
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (ByteString
pbs,) (Either DecoderError (ChainDepState (ConsensusProtocol era))
-> Either
(ByteString, DecoderError) (ChainDepState (ConsensusProtocol era)))
-> Either DecoderError (ChainDepState (ConsensusProtocol era))
-> Either
(ByteString, DecoderError) (ChainDepState (ConsensusProtocol era))
forall a b. (a -> b) -> a -> b
$ ByteString
-> Either DecoderError (ChainDepState (ConsensusProtocol era))
forall a. FromCBOR a => ByteString -> Either DecoderError a
decodeFull ByteString
pbs
newtype SerialisedCurrentEpochState era
= SerialisedCurrentEpochState (Serialised (Shelley.EpochState (ShelleyLedgerEra era)))
newtype CurrentEpochState era = CurrentEpochState (Shelley.EpochState (ShelleyLedgerEra era))
decodeCurrentEpochState
:: forall era. Ledger.Era (ShelleyLedgerEra era)
=> Share (Core.TxOut (ShelleyLedgerEra era)) ~ Interns (Shelley.Credential 'Shelley.Staking (Ledger.Crypto (ShelleyLedgerEra era)))
=> FromSharedCBOR (Core.TxOut (ShelleyLedgerEra era))
=> Share (Core.TxOut (ShelleyLedgerEra era)) ~ Interns (Shelley.Credential 'Shelley.Staking (Ledger.Crypto (ShelleyLedgerEra era)))
=> FromCBOR (Core.PParams (ShelleyLedgerEra era))
=> FromCBOR (Core.Value (ShelleyLedgerEra era))
=> FromCBOR (Ledger.State (Core.EraRule "PPUP" (ShelleyLedgerEra era)))
=> SerialisedCurrentEpochState era
-> Either DecoderError (CurrentEpochState era)
decodeCurrentEpochState :: SerialisedCurrentEpochState era
-> Either DecoderError (CurrentEpochState era)
decodeCurrentEpochState (SerialisedCurrentEpochState (Serialised ByteString
ls)) = EpochState (ShelleyLedgerEra era) -> CurrentEpochState era
forall era.
EpochState (ShelleyLedgerEra era) -> CurrentEpochState era
CurrentEpochState (EpochState (ShelleyLedgerEra era) -> CurrentEpochState era)
-> Either DecoderError (EpochState (ShelleyLedgerEra era))
-> Either DecoderError (CurrentEpochState era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> Either DecoderError (EpochState (ShelleyLedgerEra era))
forall a. FromCBOR a => ByteString -> Either DecoderError a
decodeFull ByteString
ls
toShelleyAddrSet :: CardanoEra era
-> Set AddressAny
-> Set (Shelley.Addr Consensus.StandardCrypto)
toShelleyAddrSet :: CardanoEra era -> Set AddressAny -> Set (Addr StandardCrypto)
toShelleyAddrSet CardanoEra era
era =
[Addr StandardCrypto] -> Set (Addr StandardCrypto)
forall a. Ord a => [a] -> Set a
Set.fromList
([Addr StandardCrypto] -> Set (Addr StandardCrypto))
-> (Set AddressAny -> [Addr StandardCrypto])
-> Set AddressAny
-> Set (Addr StandardCrypto)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AddressInEra era -> Addr StandardCrypto)
-> [AddressInEra era] -> [Addr StandardCrypto]
forall a b. (a -> b) -> [a] -> [b]
map AddressInEra era -> Addr StandardCrypto
forall era. AddressInEra era -> Addr StandardCrypto
toShelleyAddr
([AddressInEra era] -> [Addr StandardCrypto])
-> (Set AddressAny -> [AddressInEra era])
-> Set AddressAny
-> [Addr StandardCrypto]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AddressAny -> Maybe (AddressInEra era))
-> [AddressAny] -> [AddressInEra era]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (CardanoEra era -> AddressAny -> Maybe (AddressInEra era)
forall era.
CardanoEra era -> AddressAny -> Maybe (AddressInEra era)
anyAddressInEra CardanoEra era
era)
([AddressAny] -> [AddressInEra era])
-> (Set AddressAny -> [AddressAny])
-> Set AddressAny
-> [AddressInEra era]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set AddressAny -> [AddressAny]
forall a. Set a -> [a]
Set.toList
toLedgerUTxO :: ShelleyLedgerEra era ~ ledgerera
=> Ledger.Crypto ledgerera ~ StandardCrypto
=> ShelleyBasedEra era
-> UTxO era
-> Shelley.UTxO ledgerera
toLedgerUTxO :: ShelleyBasedEra era -> UTxO era -> UTxO ledgerera
toLedgerUTxO ShelleyBasedEra era
era (UTxO Map TxIn (TxOut CtxUTxO era)
utxo) =
Map (TxIn StandardCrypto) (TxOut ledgerera) -> UTxO ledgerera
forall era. Map (TxIn (Crypto era)) (TxOut era) -> UTxO era
Shelley.UTxO
(Map (TxIn StandardCrypto) (TxOut ledgerera) -> UTxO ledgerera)
-> (Map TxIn (TxOut CtxUTxO era)
-> Map (TxIn StandardCrypto) (TxOut ledgerera))
-> Map TxIn (TxOut CtxUTxO era)
-> UTxO ledgerera
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(TxIn StandardCrypto, TxOut ledgerera)]
-> Map (TxIn StandardCrypto) (TxOut ledgerera)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
([(TxIn StandardCrypto, TxOut ledgerera)]
-> Map (TxIn StandardCrypto) (TxOut ledgerera))
-> (Map TxIn (TxOut CtxUTxO era)
-> [(TxIn StandardCrypto, TxOut ledgerera)])
-> Map TxIn (TxOut CtxUTxO era)
-> Map (TxIn StandardCrypto) (TxOut ledgerera)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TxIn, TxOut CtxUTxO era)
-> (TxIn StandardCrypto, TxOut ledgerera))
-> [(TxIn, TxOut CtxUTxO era)]
-> [(TxIn StandardCrypto, TxOut ledgerera)]
forall a b. (a -> b) -> [a] -> [b]
map ((TxIn -> TxIn StandardCrypto)
-> (TxOut CtxUTxO era -> TxOut ledgerera)
-> (TxIn, TxOut CtxUTxO era)
-> (TxIn StandardCrypto, TxOut ledgerera)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap TxIn -> TxIn StandardCrypto
toShelleyTxIn (ShelleyBasedEra era -> TxOut CtxUTxO era -> TxOut ledgerera
forall era ledgerera.
(ShelleyLedgerEra era ~ ledgerera) =>
ShelleyBasedEra era -> TxOut CtxUTxO era -> TxOut ledgerera
toShelleyTxOut ShelleyBasedEra era
era))
([(TxIn, TxOut CtxUTxO era)]
-> [(TxIn StandardCrypto, TxOut ledgerera)])
-> (Map TxIn (TxOut CtxUTxO era) -> [(TxIn, TxOut CtxUTxO era)])
-> Map TxIn (TxOut CtxUTxO era)
-> [(TxIn StandardCrypto, TxOut ledgerera)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map TxIn (TxOut CtxUTxO era) -> [(TxIn, TxOut CtxUTxO era)]
forall k a. Map k a -> [(k, a)]
Map.toList
(Map TxIn (TxOut CtxUTxO era) -> UTxO ledgerera)
-> Map TxIn (TxOut CtxUTxO era) -> UTxO ledgerera
forall a b. (a -> b) -> a -> b
$ Map TxIn (TxOut CtxUTxO era)
utxo
fromLedgerUTxO :: ShelleyLedgerEra era ~ ledgerera
=> Ledger.Crypto ledgerera ~ StandardCrypto
=> ShelleyBasedEra era
-> Shelley.UTxO ledgerera
-> UTxO era
fromLedgerUTxO :: ShelleyBasedEra era -> UTxO ledgerera -> UTxO era
fromLedgerUTxO ShelleyBasedEra era
era (Shelley.UTxO Map (TxIn (Crypto ledgerera)) (TxOut ledgerera)
utxo) =
Map TxIn (TxOut CtxUTxO era) -> UTxO era
forall era. Map TxIn (TxOut CtxUTxO era) -> UTxO era
UTxO
(Map TxIn (TxOut CtxUTxO era) -> UTxO era)
-> (Map (TxIn StandardCrypto) (TxOut ledgerera)
-> Map TxIn (TxOut CtxUTxO era))
-> Map (TxIn StandardCrypto) (TxOut ledgerera)
-> UTxO era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(TxIn, TxOut CtxUTxO era)] -> Map TxIn (TxOut CtxUTxO era)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
([(TxIn, TxOut CtxUTxO era)] -> Map TxIn (TxOut CtxUTxO era))
-> (Map (TxIn StandardCrypto) (TxOut ledgerera)
-> [(TxIn, TxOut CtxUTxO era)])
-> Map (TxIn StandardCrypto) (TxOut ledgerera)
-> Map TxIn (TxOut CtxUTxO era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TxIn StandardCrypto, TxOut ledgerera)
-> (TxIn, TxOut CtxUTxO era))
-> [(TxIn StandardCrypto, TxOut ledgerera)]
-> [(TxIn, TxOut CtxUTxO era)]
forall a b. (a -> b) -> [a] -> [b]
map ((TxIn StandardCrypto -> TxIn)
-> (TxOut ledgerera -> TxOut CtxUTxO era)
-> (TxIn StandardCrypto, TxOut ledgerera)
-> (TxIn, TxOut CtxUTxO era)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap TxIn StandardCrypto -> TxIn
fromShelleyTxIn (ShelleyBasedEra era -> TxOut ledgerera -> TxOut CtxUTxO era
forall era ledgerera ctx.
(ShelleyLedgerEra era ~ ledgerera) =>
ShelleyBasedEra era -> TxOut ledgerera -> TxOut ctx era
fromShelleyTxOut ShelleyBasedEra era
era))
([(TxIn StandardCrypto, TxOut ledgerera)]
-> [(TxIn, TxOut CtxUTxO era)])
-> (Map (TxIn StandardCrypto) (TxOut ledgerera)
-> [(TxIn StandardCrypto, TxOut ledgerera)])
-> Map (TxIn StandardCrypto) (TxOut ledgerera)
-> [(TxIn, TxOut CtxUTxO era)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map (TxIn StandardCrypto) (TxOut ledgerera)
-> [(TxIn StandardCrypto, TxOut ledgerera)]
forall k a. Map k a -> [(k, a)]
Map.toList
(Map (TxIn StandardCrypto) (TxOut ledgerera) -> UTxO era)
-> Map (TxIn StandardCrypto) (TxOut ledgerera) -> UTxO era
forall a b. (a -> b) -> a -> b
$ Map (TxIn StandardCrypto) (TxOut ledgerera)
Map (TxIn (Crypto ledgerera)) (TxOut ledgerera)
utxo
fromShelleyPoolDistr :: Shelley.PoolDistr StandardCrypto
-> Map (Hash StakePoolKey) Rational
fromShelleyPoolDistr :: PoolDistr StandardCrypto -> Map (Hash StakePoolKey) Rational
fromShelleyPoolDistr =
[(Hash StakePoolKey, Rational)] -> Map (Hash StakePoolKey) Rational
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
([(Hash StakePoolKey, Rational)]
-> Map (Hash StakePoolKey) Rational)
-> (PoolDistr StandardCrypto -> [(Hash StakePoolKey, Rational)])
-> PoolDistr StandardCrypto
-> Map (Hash StakePoolKey) Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((KeyHash 'StakePool StandardCrypto,
IndividualPoolStake StandardCrypto)
-> (Hash StakePoolKey, Rational))
-> [(KeyHash 'StakePool StandardCrypto,
IndividualPoolStake StandardCrypto)]
-> [(Hash StakePoolKey, Rational)]
forall a b. (a -> b) -> [a] -> [b]
map ((KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey)
-> (IndividualPoolStake StandardCrypto -> Rational)
-> (KeyHash 'StakePool StandardCrypto,
IndividualPoolStake StandardCrypto)
-> (Hash StakePoolKey, Rational)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey
StakePoolKeyHash IndividualPoolStake StandardCrypto -> Rational
forall crypto. IndividualPoolStake crypto -> Rational
Shelley.individualPoolStake)
([(KeyHash 'StakePool StandardCrypto,
IndividualPoolStake StandardCrypto)]
-> [(Hash StakePoolKey, Rational)])
-> (PoolDistr StandardCrypto
-> [(KeyHash 'StakePool StandardCrypto,
IndividualPoolStake StandardCrypto)])
-> PoolDistr StandardCrypto
-> [(Hash StakePoolKey, Rational)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map
(KeyHash 'StakePool StandardCrypto)
(IndividualPoolStake StandardCrypto)
-> [(KeyHash 'StakePool StandardCrypto,
IndividualPoolStake StandardCrypto)]
forall k a. Map k a -> [(k, a)]
Map.toList
(Map
(KeyHash 'StakePool StandardCrypto)
(IndividualPoolStake StandardCrypto)
-> [(KeyHash 'StakePool StandardCrypto,
IndividualPoolStake StandardCrypto)])
-> (PoolDistr StandardCrypto
-> Map
(KeyHash 'StakePool StandardCrypto)
(IndividualPoolStake StandardCrypto))
-> PoolDistr StandardCrypto
-> [(KeyHash 'StakePool StandardCrypto,
IndividualPoolStake StandardCrypto)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PoolDistr StandardCrypto
-> Map
(KeyHash 'StakePool StandardCrypto)
(IndividualPoolStake StandardCrypto)
forall crypto.
PoolDistr crypto
-> Map (KeyHash 'StakePool crypto) (IndividualPoolStake crypto)
Shelley.unPoolDistr
fromShelleyDelegations :: Map (Shelley.Credential Shelley.Staking StandardCrypto)
(Shelley.KeyHash Shelley.StakePool StandardCrypto)
-> Map StakeCredential PoolId
fromShelleyDelegations :: Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
-> Map StakeCredential (Hash StakePoolKey)
fromShelleyDelegations =
[(StakeCredential, Hash StakePoolKey)]
-> Map StakeCredential (Hash StakePoolKey)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
([(StakeCredential, Hash StakePoolKey)]
-> Map StakeCredential (Hash StakePoolKey))
-> (Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
-> [(StakeCredential, Hash StakePoolKey)])
-> Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
-> Map StakeCredential (Hash StakePoolKey)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Credential 'Staking StandardCrypto,
KeyHash 'StakePool StandardCrypto)
-> (StakeCredential, Hash StakePoolKey))
-> [(Credential 'Staking StandardCrypto,
KeyHash 'StakePool StandardCrypto)]
-> [(StakeCredential, Hash StakePoolKey)]
forall a b. (a -> b) -> [a] -> [b]
map ((Credential 'Staking StandardCrypto -> StakeCredential)
-> (KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey)
-> (Credential 'Staking StandardCrypto,
KeyHash 'StakePool StandardCrypto)
-> (StakeCredential, Hash StakePoolKey)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Credential 'Staking StandardCrypto -> StakeCredential
fromShelleyStakeCredential KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey
StakePoolKeyHash)
([(Credential 'Staking StandardCrypto,
KeyHash 'StakePool StandardCrypto)]
-> [(StakeCredential, Hash StakePoolKey)])
-> (Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
-> [(Credential 'Staking StandardCrypto,
KeyHash 'StakePool StandardCrypto)])
-> Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
-> [(StakeCredential, Hash StakePoolKey)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
-> [(Credential 'Staking StandardCrypto,
KeyHash 'StakePool StandardCrypto)]
forall k a. Map k a -> [(k, a)]
Map.toList
fromShelleyRewardAccounts :: Shelley.RewardAccounts Consensus.StandardCrypto
-> Map StakeCredential Lovelace
fromShelleyRewardAccounts :: RewardAccounts StandardCrypto -> Map StakeCredential Lovelace
fromShelleyRewardAccounts =
[(StakeCredential, Lovelace)] -> Map StakeCredential Lovelace
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
([(StakeCredential, Lovelace)] -> Map StakeCredential Lovelace)
-> (RewardAccounts StandardCrypto -> [(StakeCredential, Lovelace)])
-> RewardAccounts StandardCrypto
-> Map StakeCredential Lovelace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Credential 'Staking StandardCrypto, Coin)
-> (StakeCredential, Lovelace))
-> [(Credential 'Staking StandardCrypto, Coin)]
-> [(StakeCredential, Lovelace)]
forall a b. (a -> b) -> [a] -> [b]
map ((Credential 'Staking StandardCrypto -> StakeCredential)
-> (Coin -> Lovelace)
-> (Credential 'Staking StandardCrypto, Coin)
-> (StakeCredential, Lovelace)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Credential 'Staking StandardCrypto -> StakeCredential
fromShelleyStakeCredential Coin -> Lovelace
fromShelleyLovelace)
([(Credential 'Staking StandardCrypto, Coin)]
-> [(StakeCredential, Lovelace)])
-> (RewardAccounts StandardCrypto
-> [(Credential 'Staking StandardCrypto, Coin)])
-> RewardAccounts StandardCrypto
-> [(StakeCredential, Lovelace)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RewardAccounts StandardCrypto
-> [(Credential 'Staking StandardCrypto, Coin)]
forall k a. Map k a -> [(k, a)]
Map.toList
toConsensusQuery :: forall mode block result.
ConsensusBlockForMode mode ~ block
=> QueryInMode mode result
-> Some (Consensus.Query block)
toConsensusQuery :: QueryInMode mode result -> Some (Query block)
toConsensusQuery (QueryCurrentEra ConsensusModeIsMultiEra mode
CardanoModeIsMultiEra) =
Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Some
(Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto)))
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Some
(Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))))
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Some
(Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto)))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
forall blk result. BlockQuery blk result -> Query blk result
Consensus.BlockQuery (BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto)))
-> BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
forall a b. (a -> b) -> a -> b
$
QueryHardFork
(ByronBlock : CardanoShelleyEras StandardCrypto)
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
-> BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
forall (xs1 :: [*]) x a.
IsNonEmpty xs1 =>
QueryHardFork (x : xs1) a -> BlockQuery (HardForkBlock (x : xs1)) a
Consensus.QueryHardFork
QueryHardFork
(ByronBlock : CardanoShelleyEras StandardCrypto)
(EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto))
forall (xs :: [*]). QueryHardFork xs (EraIndex xs)
Consensus.GetCurrentEra
toConsensusQuery (QueryInEra EraInMode era mode
ByronEraInByronMode QueryInEra era result
QueryByronUpdateState) =
Query
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State)
-> Some (Query (HardForkBlock '[ByronBlock]))
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (Query
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State)
-> Some (Query (HardForkBlock '[ByronBlock])))
-> Query
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State)
-> Some (Query (HardForkBlock '[ByronBlock]))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State)
-> Query
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State)
forall blk result. BlockQuery blk result -> Query blk result
Consensus.BlockQuery (BlockQuery
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State)
-> Query
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State))
-> BlockQuery
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State)
-> Query
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State)
forall a b. (a -> b) -> a -> b
$
BlockQuery ByronBlock State
-> BlockQuery
(HardForkBlock '[ByronBlock])
(HardForkQueryResult '[ByronBlock] State)
forall b a result.
(HardForkQueryResult '[b] result ~ a) =>
BlockQuery b result -> BlockQuery (HardForkBlock '[b]) a
Consensus.DegenQuery
BlockQuery ByronBlock State
Consensus.GetUpdateInterfaceState
toConsensusQuery (QueryEraHistory ConsensusModeIsMultiEra mode
CardanoModeIsMultiEra) =
Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Some
(Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto)))
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Some
(Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))))
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Some
(Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto)))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
forall blk result. BlockQuery blk result -> Query blk result
Consensus.BlockQuery (BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto)))
-> BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
forall a b. (a -> b) -> a -> b
$
QueryHardFork
(ByronBlock : CardanoShelleyEras StandardCrypto)
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
-> BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
forall (xs1 :: [*]) x a.
IsNonEmpty xs1 =>
QueryHardFork (x : xs1) a -> BlockQuery (HardForkBlock (x : xs1)) a
Consensus.QueryHardFork
QueryHardFork
(ByronBlock : CardanoShelleyEras StandardCrypto)
(Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto))
forall (xs :: [*]). QueryHardFork xs (Interpreter xs)
Consensus.GetInterpreter
toConsensusQuery QueryInMode mode result
QuerySystemStart = Query block SystemStart -> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some Query block SystemStart
forall blk. Query blk SystemStart
Consensus.GetSystemStart
toConsensusQuery QueryInMode mode result
QueryChainBlockNo = Query block (WithOrigin BlockNo) -> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some Query block (WithOrigin BlockNo)
forall blk. Query blk (WithOrigin BlockNo)
Consensus.GetChainBlockNo
toConsensusQuery (QueryChainPoint ConsensusMode mode
_) = Query block (Point block) -> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some Query block (Point block)
forall blk. Query blk (Point blk)
Consensus.GetChainPoint
toConsensusQuery (QueryInEra EraInMode era mode
ByronEraInCardanoMode QueryInEra era result
QueryByronUpdateState) =
Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State)
-> Some
(Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto)))
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State)
-> Some
(Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))))
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State)
-> Some
(Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto)))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State)
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State)
forall blk result. BlockQuery blk result -> Query blk result
Consensus.BlockQuery (BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State)
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State))
-> BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State)
-> Query
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State)
forall a b. (a -> b) -> a -> b
$
BlockQuery ByronBlock State
-> BlockQuery
(HardForkBlock (ByronBlock : CardanoShelleyEras StandardCrypto))
(CardanoQueryResult StandardCrypto State)
forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery ByronBlock result -> CardanoQuery c a
Consensus.QueryIfCurrentByron
BlockQuery ByronBlock State
Consensus.GetUpdateInterfaceState
toConsensusQuery (QueryInEra EraInMode era mode
erainmode (QueryInShelleyBasedEra ShelleyBasedEra era
era QueryInShelleyBasedEra era result
q)) =
case EraInMode era mode
erainmode of
EraInMode era mode
ByronEraInByronMode -> case ShelleyBasedEra era
era of {}
EraInMode era mode
ShelleyEraInShelleyMode -> EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
forall era ledgerera mode protocol block (xs :: [*]) result.
(ConsensusBlockForEra era ~ ShelleyBlock protocol ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
q
EraInMode era mode
ByronEraInCardanoMode -> case ShelleyBasedEra era
era of {}
EraInMode era mode
ShelleyEraInCardanoMode -> EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
forall era ledgerera mode protocol block (xs :: [*]) result.
(ConsensusBlockForEra era ~ ShelleyBlock protocol ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
q
EraInMode era mode
AllegraEraInCardanoMode -> EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
forall era ledgerera mode protocol block (xs :: [*]) result.
(ConsensusBlockForEra era ~ ShelleyBlock protocol ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
q
EraInMode era mode
MaryEraInCardanoMode -> EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
forall era ledgerera mode protocol block (xs :: [*]) result.
(ConsensusBlockForEra era ~ ShelleyBlock protocol ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
q
EraInMode era mode
AlonzoEraInCardanoMode -> EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
forall era ledgerera mode protocol block (xs :: [*]) result.
(ConsensusBlockForEra era ~ ShelleyBlock protocol ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
q
EraInMode era mode
BabbageEraInCardanoMode -> EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
forall era ledgerera mode protocol block (xs :: [*]) result.
(ConsensusBlockForEra era ~ ShelleyBlock protocol ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
q
toConsensusQueryShelleyBased
:: forall era ledgerera mode protocol block xs result.
ConsensusBlockForEra era ~ Consensus.ShelleyBlock protocol ledgerera
=> Ledger.Crypto ledgerera ~ Consensus.StandardCrypto
=> ConsensusBlockForMode mode ~ block
=> block ~ Consensus.HardForkBlock xs
=> EraInMode era mode
-> QueryInShelleyBasedEra era result
-> Some (Consensus.Query block)
toConsensusQueryShelleyBased :: EraInMode era mode
-> QueryInShelleyBasedEra era result -> Some (Query block)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
QueryEpoch =
Query block (HardForkQueryResult xs EpochNo) -> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery (ShelleyBlock protocol ledgerera) EpochNo
-> Query block (HardForkQueryResult xs EpochNo)
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode BlockQuery (ShelleyBlock protocol ledgerera) EpochNo
forall proto era. BlockQuery (ShelleyBlock proto era) EpochNo
Consensus.GetEpochNo)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
QueryGenesisParameters =
Query block (HardForkQueryResult xs (CompactGenesis ledgerera))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(ShelleyBlock protocol ledgerera) (CompactGenesis ledgerera)
-> Query block (HardForkQueryResult xs (CompactGenesis ledgerera))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode BlockQuery
(ShelleyBlock protocol ledgerera) (CompactGenesis ledgerera)
forall proto era.
BlockQuery (ShelleyBlock proto era) (CompactGenesis era)
Consensus.GetGenesisConfig)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
QueryProtocolParameters =
Query block (HardForkQueryResult xs (PParams ledgerera))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery (ShelleyBlock protocol ledgerera) (PParams ledgerera)
-> Query block (HardForkQueryResult xs (PParams ledgerera))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode BlockQuery (ShelleyBlock protocol ledgerera) (PParams ledgerera)
forall proto era. BlockQuery (ShelleyBlock proto era) (PParams era)
Consensus.GetCurrentPParams)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
QueryProtocolParametersUpdate =
Query block (HardForkQueryResult xs (ProposedPPUpdates ledgerera))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(ShelleyBlock protocol ledgerera) (ProposedPPUpdates ledgerera)
-> Query
block (HardForkQueryResult xs (ProposedPPUpdates ledgerera))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode BlockQuery
(ShelleyBlock protocol ledgerera) (ProposedPPUpdates ledgerera)
forall proto era.
BlockQuery (ShelleyBlock proto era) (ProposedPPUpdates era)
Consensus.GetProposedPParamsUpdates)
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
QueryStakeDistribution =
Query block (HardForkQueryResult xs (PoolDistr StandardCrypto))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(ShelleyBlock protocol ledgerera) (PoolDistr StandardCrypto)
-> Query block (HardForkQueryResult xs (PoolDistr StandardCrypto))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode BlockQuery
(ShelleyBlock protocol ledgerera) (PoolDistr StandardCrypto)
forall proto era.
BlockQuery (ShelleyBlock proto era) (PoolDistr (EraCrypto era))
Consensus.GetStakeDistribution)
toConsensusQueryShelleyBased EraInMode era mode
erainmode (QueryUTxO QueryUTxOFilter
QueryUTxOWhole) =
Query block (HardForkQueryResult xs (UTxO ledgerera))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery (ShelleyBlock protocol ledgerera) (UTxO ledgerera)
-> Query block (HardForkQueryResult xs (UTxO ledgerera))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode BlockQuery (ShelleyBlock protocol ledgerera) (UTxO ledgerera)
forall proto era. BlockQuery (ShelleyBlock proto era) (UTxO era)
Consensus.GetUTxOWhole)
toConsensusQueryShelleyBased EraInMode era mode
erainmode (QueryUTxO (QueryUTxOByAddress Set AddressAny
addrs)) =
Query block (HardForkQueryResult xs (UTxO ledgerera))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery (ShelleyBlock protocol ledgerera) (UTxO ledgerera)
-> Query block (HardForkQueryResult xs (UTxO ledgerera))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode (Set (Addr (EraCrypto ledgerera))
-> BlockQuery (ShelleyBlock protocol ledgerera) (UTxO ledgerera)
forall era proto.
Set (Addr (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (UTxO era)
Consensus.GetUTxOByAddress Set (Addr StandardCrypto)
Set (Addr (EraCrypto ledgerera))
addrs'))
where
addrs' :: Set (Shelley.Addr Consensus.StandardCrypto)
addrs' :: Set (Addr StandardCrypto)
addrs' = CardanoEra era -> Set AddressAny -> Set (Addr StandardCrypto)
forall era.
CardanoEra era -> Set AddressAny -> Set (Addr StandardCrypto)
toShelleyAddrSet (EraInMode era mode -> CardanoEra era
forall era mode. EraInMode era mode -> CardanoEra era
eraInModeToEra EraInMode era mode
erainmode) Set AddressAny
addrs
toConsensusQueryShelleyBased EraInMode era mode
erainmode (QueryUTxO (QueryUTxOByTxIn Set TxIn
txins)) =
Query block (HardForkQueryResult xs (UTxO ledgerera))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery (ShelleyBlock protocol ledgerera) (UTxO ledgerera)
-> Query block (HardForkQueryResult xs (UTxO ledgerera))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode (Set (TxIn (EraCrypto ledgerera))
-> BlockQuery (ShelleyBlock protocol ledgerera) (UTxO ledgerera)
forall era proto.
Set (TxIn (EraCrypto era))
-> BlockQuery (ShelleyBlock proto era) (UTxO era)
Consensus.GetUTxOByTxIn Set (TxIn StandardCrypto)
Set (TxIn (EraCrypto ledgerera))
txins'))
where
txins' :: Set (Shelley.TxIn Consensus.StandardCrypto)
txins' :: Set (TxIn StandardCrypto)
txins' = (TxIn -> TxIn StandardCrypto)
-> Set TxIn -> Set (TxIn StandardCrypto)
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map TxIn -> TxIn StandardCrypto
toShelleyTxIn Set TxIn
txins
toConsensusQueryShelleyBased EraInMode era mode
erainmode (QueryStakeAddresses Set StakeCredential
creds NetworkId
_nId) =
Query
block
(HardForkQueryResult
xs
(Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto),
RewardAccounts StandardCrypto))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto),
RewardAccounts StandardCrypto)
-> Query
block
(HardForkQueryResult
xs
(Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto),
RewardAccounts StandardCrypto))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode
(Set (Credential 'Staking (EraCrypto ledgerera))
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Delegations (EraCrypto ledgerera),
RewardAccounts (EraCrypto ledgerera))
forall era proto.
Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Delegations (EraCrypto era), RewardAccounts (EraCrypto era))
Consensus.GetFilteredDelegationsAndRewardAccounts Set (Credential 'Staking StandardCrypto)
Set (Credential 'Staking (EraCrypto ledgerera))
creds'))
where
creds' :: Set (Shelley.Credential Shelley.Staking StandardCrypto)
creds' :: Set (Credential 'Staking StandardCrypto)
creds' = (StakeCredential -> Credential 'Staking StandardCrypto)
-> Set StakeCredential -> Set (Credential 'Staking StandardCrypto)
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map StakeCredential -> Credential 'Staking StandardCrypto
toShelleyStakeCredential Set StakeCredential
creds
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
QueryStakePools =
Query
block
(HardForkQueryResult xs (Set (KeyHash 'StakePool StandardCrypto)))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Set (KeyHash 'StakePool StandardCrypto))
-> Query
block
(HardForkQueryResult xs (Set (KeyHash 'StakePool StandardCrypto)))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode BlockQuery
(ShelleyBlock protocol ledgerera)
(Set (KeyHash 'StakePool StandardCrypto))
forall proto era.
BlockQuery
(ShelleyBlock proto era) (Set (KeyHash 'StakePool (EraCrypto era)))
Consensus.GetStakePools)
toConsensusQueryShelleyBased EraInMode era mode
erainmode (QueryStakePoolParameters Set (Hash StakePoolKey)
poolids) =
Query
block
(HardForkQueryResult
xs
(Map
(KeyHash 'StakePool StandardCrypto) (PoolParams StandardCrypto)))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Map
(KeyHash 'StakePool StandardCrypto) (PoolParams StandardCrypto))
-> Query
block
(HardForkQueryResult
xs
(Map
(KeyHash 'StakePool StandardCrypto) (PoolParams StandardCrypto)))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode (Set (KeyHash 'StakePool (EraCrypto ledgerera))
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Map
(KeyHash 'StakePool (EraCrypto ledgerera))
(PoolParams (EraCrypto ledgerera)))
forall era proto.
Set (KeyHash 'StakePool (EraCrypto era))
-> BlockQuery
(ShelleyBlock proto era)
(Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era)))
Consensus.GetStakePoolParams Set (KeyHash 'StakePool StandardCrypto)
Set (KeyHash 'StakePool (EraCrypto ledgerera))
poolids'))
where
poolids' :: Set (Shelley.KeyHash Shelley.StakePool Consensus.StandardCrypto)
poolids' :: Set (KeyHash 'StakePool StandardCrypto)
poolids' = (Hash StakePoolKey -> KeyHash 'StakePool StandardCrypto)
-> Set (Hash StakePoolKey)
-> Set (KeyHash 'StakePool StandardCrypto)
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map (\(StakePoolKeyHash kh) -> KeyHash 'StakePool StandardCrypto
kh) Set (Hash StakePoolKey)
poolids
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
QueryDebugLedgerState =
Query
block
(HardForkQueryResult xs (Serialised (NewEpochState ledgerera)))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Serialised (NewEpochState ledgerera))
-> Query
block
(HardForkQueryResult xs (Serialised (NewEpochState ledgerera)))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode (BlockQuery
(ShelleyBlock protocol ledgerera) (NewEpochState ledgerera)
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Serialised (NewEpochState ledgerera))
forall proto era result.
BlockQuery (ShelleyBlock proto era) result
-> BlockQuery (ShelleyBlock proto era) (Serialised result)
Consensus.GetCBOR BlockQuery
(ShelleyBlock protocol ledgerera) (NewEpochState ledgerera)
forall proto era.
BlockQuery (ShelleyBlock proto era) (NewEpochState era)
Consensus.DebugNewEpochState))
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
QueryProtocolState =
Query
block
(HardForkQueryResult xs (Serialised (ChainDepState protocol)))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Serialised (ChainDepState protocol))
-> Query
block
(HardForkQueryResult xs (Serialised (ChainDepState protocol)))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode (BlockQuery
(ShelleyBlock protocol ledgerera) (ChainDepState protocol)
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Serialised (ChainDepState protocol))
forall proto era result.
BlockQuery (ShelleyBlock proto era) result
-> BlockQuery (ShelleyBlock proto era) (Serialised result)
Consensus.GetCBOR BlockQuery
(ShelleyBlock protocol ledgerera) (ChainDepState protocol)
forall proto era.
BlockQuery (ShelleyBlock proto era) (ChainDepState proto)
Consensus.DebugChainDepState))
toConsensusQueryShelleyBased EraInMode era mode
erainmode QueryInShelleyBasedEra era result
QueryCurrentEpochState =
Query
block (HardForkQueryResult xs (Serialised (EpochState ledgerera)))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Serialised (EpochState ledgerera))
-> Query
block (HardForkQueryResult xs (Serialised (EpochState ledgerera)))
forall era mode erablock modeblock result result' (xs :: [*]).
(ConsensusBlockForEra era ~ erablock,
ConsensusBlockForMode mode ~ modeblock,
modeblock ~ HardForkBlock xs,
HardForkQueryResult xs result ~ result') =>
EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode (BlockQuery (ShelleyBlock protocol ledgerera) (EpochState ledgerera)
-> BlockQuery
(ShelleyBlock protocol ledgerera)
(Serialised (EpochState ledgerera))
forall proto era result.
BlockQuery (ShelleyBlock proto era) result
-> BlockQuery (ShelleyBlock proto era) (Serialised result)
Consensus.GetCBOR BlockQuery (ShelleyBlock protocol ledgerera) (EpochState ledgerera)
forall proto era.
BlockQuery (ShelleyBlock proto era) (EpochState era)
Consensus.DebugEpochState))
consensusQueryInEraInMode
:: forall era mode erablock modeblock result result' xs.
ConsensusBlockForEra era ~ erablock
=> ConsensusBlockForMode mode ~ modeblock
=> modeblock ~ Consensus.HardForkBlock xs
=> Consensus.HardForkQueryResult xs result ~ result'
=> EraInMode era mode
-> Consensus.BlockQuery erablock result
-> Consensus.Query modeblock result'
consensusQueryInEraInMode :: EraInMode era mode
-> BlockQuery erablock result -> Query modeblock result'
consensusQueryInEraInMode EraInMode era mode
erainmode =
BlockQuery modeblock result' -> Query modeblock result'
forall blk result. BlockQuery blk result -> Query blk result
Consensus.BlockQuery
(BlockQuery modeblock result' -> Query modeblock result')
-> (BlockQuery erablock result -> BlockQuery modeblock result')
-> BlockQuery erablock result
-> Query modeblock result'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. case EraInMode era mode
erainmode of
EraInMode era mode
ByronEraInByronMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall b a result.
(HardForkQueryResult '[b] result ~ a) =>
BlockQuery b result -> BlockQuery (HardForkBlock '[b]) a
Consensus.DegenQuery
EraInMode era mode
ShelleyEraInShelleyMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall b a result.
(HardForkQueryResult '[b] result ~ a) =>
BlockQuery b result -> BlockQuery (HardForkBlock '[b]) a
Consensus.DegenQuery
EraInMode era mode
ByronEraInCardanoMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery ByronBlock result -> CardanoQuery c a
Consensus.QueryIfCurrentByron
EraInMode era mode
ShelleyEraInCardanoMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (ShelleyEra c)) result
-> CardanoQuery c a
Consensus.QueryIfCurrentShelley
EraInMode era mode
AllegraEraInCardanoMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (AllegraEra c)) result
-> CardanoQuery c a
Consensus.QueryIfCurrentAllegra
EraInMode era mode
MaryEraInCardanoMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (MaryEra c)) result
-> CardanoQuery c a
Consensus.QueryIfCurrentMary
EraInMode era mode
AlonzoEraInCardanoMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (AlonzoEra c)) result
-> CardanoQuery c a
Consensus.QueryIfCurrentAlonzo
EraInMode era mode
BabbageEraInCardanoMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (Praos c) (BabbageEra c)) result
-> CardanoQuery c a
Consensus.QueryIfCurrentBabbage
fromConsensusQueryResult :: forall mode block result result'. ConsensusBlockForMode mode ~ block
=> QueryInMode mode result
-> Consensus.Query block result'
-> result'
-> result
fromConsensusQueryResult :: QueryInMode mode result -> Query block result' -> result' -> result
fromConsensusQueryResult (QueryEraHistory ConsensusModeIsMultiEra mode
CardanoModeIsMultiEra) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryHardFork Consensus.GetInterpreter)
-> ConsensusMode CardanoMode
-> Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraHistory CardanoMode
forall mode (xs :: [*]).
(ConsensusBlockForMode mode ~ HardForkBlock xs) =>
ConsensusMode mode -> Interpreter xs -> EraHistory mode
EraHistory ConsensusMode CardanoMode
CardanoMode result'
Interpreter (ByronBlock : CardanoShelleyEras StandardCrypto)
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult QueryInMode mode result
QuerySystemStart Query block result'
q' result'
r' =
case Query block result'
q' of
Query block result'
Consensus.GetSystemStart
-> result
result'
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult QueryInMode mode result
QueryChainBlockNo Query block result'
q' result'
r' =
case Query block result'
q' of
Query block result'
Consensus.GetChainBlockNo
-> result
result'
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryChainPoint ConsensusMode mode
mode) Query block result'
q' result'
r' =
case Query block result'
q' of
Query block result'
Consensus.GetChainPoint
-> ConsensusMode mode
-> Point (ConsensusBlockForMode mode) -> ChainPoint
forall mode.
ConsensusMode mode
-> Point (ConsensusBlockForMode mode) -> ChainPoint
fromConsensusPointInMode ConsensusMode mode
mode result'
Point (ConsensusBlockForMode mode)
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryCurrentEra ConsensusModeIsMultiEra mode
CardanoModeIsMultiEra) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryHardFork Consensus.GetCurrentEra)
-> AnyEraInMode CardanoMode -> AnyCardanoEra
forall mode. AnyEraInMode mode -> AnyCardanoEra
anyEraInModeToAnyEra (ConsensusMode CardanoMode
-> EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto)
-> AnyEraInMode CardanoMode
forall mode (xs :: [*]).
(ConsensusBlockForMode mode ~ HardForkBlock xs) =>
ConsensusMode mode -> EraIndex xs -> AnyEraInMode mode
fromConsensusEraIndex ConsensusMode CardanoMode
CardanoMode result'
EraIndex (ByronBlock : CardanoShelleyEras StandardCrypto)
r')
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
ByronEraInByronMode
QueryInEra era result
QueryByronUpdateState) Query block result'
q' result'
r' =
case (Query block result'
q', result'
r') of
(Consensus.BlockQuery (Consensus.DegenQuery Consensus.GetUpdateInterfaceState),
Consensus.DegenQueryResult r'')
-> ByronUpdateState -> Either EraMismatch ByronUpdateState
forall a b. b -> Either a b
Right (State -> ByronUpdateState
ByronUpdateState State
r'')
(Query block result', result')
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
ByronEraInCardanoMode
QueryInEra era result
QueryByronUpdateState) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery
(Consensus.QueryIfCurrentByron Consensus.GetUpdateInterfaceState)
-> (MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch)
-> (State -> ByronUpdateState)
-> CardanoQueryResult StandardCrypto State
-> Either EraMismatch ByronUpdateState
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch State -> ByronUpdateState
ByronUpdateState result'
CardanoQueryResult StandardCrypto State
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
ByronEraInByronMode
(QueryInShelleyBasedEra ShelleyBasedEra era
era QueryInShelleyBasedEra era result
_)) Query block result'
_ result'
_ =
case ShelleyBasedEra era
era of {}
fromConsensusQueryResult (QueryInEra EraInMode era mode
ShelleyEraInShelleyMode
(QueryInShelleyBasedEra ShelleyBasedEra era
_era QueryInShelleyBasedEra era result
q)) Query block result'
q' result'
r' =
case (Query block result'
q', result'
r') of
(Consensus.BlockQuery (Consensus.DegenQuery q''),
Consensus.DegenQueryResult r'')
-> result -> Either EraMismatch result
forall a b. b -> Either a b
Right (ShelleyBasedEra ShelleyEra
-> QueryInShelleyBasedEra ShelleyEra result
-> BlockQuery
(ShelleyBlock (TPraos StandardCrypto) StandardShelley) result
-> result
-> result
forall era ledgerera protocol result result'.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusProtocol era ~ protocol) =>
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result
-> BlockQuery (ShelleyBlock protocol ledgerera) result'
-> result'
-> result
fromConsensusQueryResultShelleyBased
ShelleyBasedEra ShelleyEra
ShelleyBasedEraShelley QueryInShelleyBasedEra era result
QueryInShelleyBasedEra ShelleyEra result
q BlockQuery
(ShelleyBlock (TPraos StandardCrypto) StandardShelley) result
q'' result
r'')
(Query block result', result')
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
ByronEraInCardanoMode
(QueryInShelleyBasedEra ShelleyBasedEra era
era QueryInShelleyBasedEra era result
_)) Query block result'
_ result'
_ =
case ShelleyBasedEra era
era of {}
fromConsensusQueryResult (QueryInEra EraInMode era mode
ShelleyEraInCardanoMode
(QueryInShelleyBasedEra ShelleyBasedEra era
_era QueryInShelleyBasedEra era result
q)) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryIfCurrentShelley q'')
-> (MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch)
-> (result -> result)
-> Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
-> Either EraMismatch result
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch
(ShelleyBasedEra ShelleyEra
-> QueryInShelleyBasedEra ShelleyEra result
-> BlockQuery
(ShelleyBlock (TPraos StandardCrypto) StandardShelley) result
-> result
-> result
forall era ledgerera protocol result result'.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusProtocol era ~ protocol) =>
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result
-> BlockQuery (ShelleyBlock protocol ledgerera) result'
-> result'
-> result
fromConsensusQueryResultShelleyBased
ShelleyBasedEra ShelleyEra
ShelleyBasedEraShelley QueryInShelleyBasedEra era result
QueryInShelleyBasedEra ShelleyEra result
q BlockQuery
(ShelleyBlock (TPraos StandardCrypto) StandardShelley) result
q'')
result'
Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
AllegraEraInCardanoMode
(QueryInShelleyBasedEra ShelleyBasedEra era
_era QueryInShelleyBasedEra era result
q)) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryIfCurrentAllegra q'')
-> (MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch)
-> (result -> result)
-> Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
-> Either EraMismatch result
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch
(ShelleyBasedEra AllegraEra
-> QueryInShelleyBasedEra AllegraEra result
-> BlockQuery
(ShelleyBlock (TPraos StandardCrypto) (AllegraEra StandardCrypto))
result
-> result
-> result
forall era ledgerera protocol result result'.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusProtocol era ~ protocol) =>
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result
-> BlockQuery (ShelleyBlock protocol ledgerera) result'
-> result'
-> result
fromConsensusQueryResultShelleyBased
ShelleyBasedEra AllegraEra
ShelleyBasedEraAllegra QueryInShelleyBasedEra era result
QueryInShelleyBasedEra AllegraEra result
q BlockQuery
(ShelleyBlock (TPraos StandardCrypto) (AllegraEra StandardCrypto))
result
q'')
result'
Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
MaryEraInCardanoMode
(QueryInShelleyBasedEra ShelleyBasedEra era
_era QueryInShelleyBasedEra era result
q)) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryIfCurrentMary q'')
-> (MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch)
-> (result -> result)
-> Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
-> Either EraMismatch result
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch
(ShelleyBasedEra MaryEra
-> QueryInShelleyBasedEra MaryEra result
-> BlockQuery
(ShelleyBlock (TPraos StandardCrypto) (MaryEra StandardCrypto))
result
-> result
-> result
forall era ledgerera protocol result result'.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusProtocol era ~ protocol) =>
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result
-> BlockQuery (ShelleyBlock protocol ledgerera) result'
-> result'
-> result
fromConsensusQueryResultShelleyBased
ShelleyBasedEra MaryEra
ShelleyBasedEraMary QueryInShelleyBasedEra era result
QueryInShelleyBasedEra MaryEra result
q BlockQuery
(ShelleyBlock (TPraos StandardCrypto) (MaryEra StandardCrypto))
result
q'')
result'
Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
AlonzoEraInCardanoMode
(QueryInShelleyBasedEra ShelleyBasedEra era
_era QueryInShelleyBasedEra era result
q)) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryIfCurrentAlonzo q'')
-> (MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch)
-> (result -> result)
-> Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
-> Either EraMismatch result
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch
(ShelleyBasedEra AlonzoEra
-> QueryInShelleyBasedEra AlonzoEra result
-> BlockQuery
(ShelleyBlock (TPraos StandardCrypto) (AlonzoEra StandardCrypto))
result
-> result
-> result
forall era ledgerera protocol result result'.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusProtocol era ~ protocol) =>
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result
-> BlockQuery (ShelleyBlock protocol ledgerera) result'
-> result'
-> result
fromConsensusQueryResultShelleyBased
ShelleyBasedEra AlonzoEra
ShelleyBasedEraAlonzo QueryInShelleyBasedEra era result
QueryInShelleyBasedEra AlonzoEra result
q BlockQuery
(ShelleyBlock (TPraos StandardCrypto) (AlonzoEra StandardCrypto))
result
q'')
result'
Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
BabbageEraInCardanoMode
(QueryInShelleyBasedEra ShelleyBasedEra era
_era QueryInShelleyBasedEra era result
q)) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryIfCurrentBabbage q'')
-> (MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch)
-> (result -> result)
-> Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
-> Either EraMismatch result
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto)
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch
(ShelleyBasedEra BabbageEra
-> QueryInShelleyBasedEra BabbageEra result
-> BlockQuery
(ShelleyBlock (Praos StandardCrypto) (BabbageEra StandardCrypto))
result
-> result
-> result
forall era ledgerera protocol result result'.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusProtocol era ~ protocol) =>
ShelleyBasedEra era
-> QueryInShelleyBasedEra era result
-> BlockQuery (ShelleyBlock protocol ledgerera) result'
-> result'
-> result
fromConsensusQueryResultShelleyBased
ShelleyBasedEra BabbageEra
ShelleyBasedEraBabbage QueryInShelleyBasedEra era result
QueryInShelleyBasedEra BabbageEra result
q BlockQuery
(ShelleyBlock (Praos StandardCrypto) (BabbageEra StandardCrypto))
result
q'')
result'
Either
(MismatchEraInfo (ByronBlock : CardanoShelleyEras StandardCrypto))
result
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased
:: forall era ledgerera protocol result result'.
ShelleyLedgerEra era ~ ledgerera
=> Ledger.Crypto ledgerera ~ Consensus.StandardCrypto
=> ConsensusProtocol era ~ protocol
=> ShelleyBasedEra era
-> QueryInShelleyBasedEra era result
-> Consensus.BlockQuery (Consensus.ShelleyBlock protocol ledgerera) result'
-> result'
-> result
fromConsensusQueryResultShelleyBased :: ShelleyBasedEra era
-> QueryInShelleyBasedEra era result
-> BlockQuery (ShelleyBlock protocol ledgerera) result'
-> result'
-> result
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
_ QueryInShelleyBasedEra era result
QueryEpoch BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
epoch =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
BlockQuery (ShelleyBlock protocol ledgerera) result'
Consensus.GetEpochNo -> result
result'
epoch
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
_ QueryInShelleyBasedEra era result
QueryGenesisParameters BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
r' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
BlockQuery (ShelleyBlock protocol ledgerera) result'
Consensus.GetGenesisConfig -> ShelleyGenesis ledgerera -> GenesisParameters
forall era. ShelleyGenesis era -> GenesisParameters
fromShelleyGenesis
(CompactGenesis ledgerera -> ShelleyGenesis ledgerera
forall era. CompactGenesis era -> ShelleyGenesis era
Consensus.getCompactGenesis result'
CompactGenesis ledgerera
r')
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
era QueryInShelleyBasedEra era result
QueryProtocolParameters BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
r' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
BlockQuery (ShelleyBlock protocol ledgerera) result'
Consensus.GetCurrentPParams -> ShelleyBasedEra era
-> PParams (ShelleyLedgerEra era) -> ProtocolParameters
forall era.
ShelleyBasedEra era
-> PParams (ShelleyLedgerEra era) -> ProtocolParameters
fromLedgerPParams ShelleyBasedEra era
era result'
PParams (ShelleyLedgerEra era)
r'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
era QueryInShelleyBasedEra era result
QueryProtocolParametersUpdate BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
r' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
BlockQuery (ShelleyBlock protocol ledgerera) result'
Consensus.GetProposedPParamsUpdates -> ShelleyBasedEra era
-> ProposedPPUpdates ledgerera
-> Map (Hash GenesisKey) ProtocolParametersUpdate
forall era ledgerera.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
ShelleyBasedEra era
-> ProposedPPUpdates ledgerera
-> Map (Hash GenesisKey) ProtocolParametersUpdate
fromLedgerProposedPPUpdates ShelleyBasedEra era
era result'
ProposedPPUpdates ledgerera
r'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
_ QueryInShelleyBasedEra era result
QueryStakeDistribution BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
r' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
BlockQuery (ShelleyBlock protocol ledgerera) result'
Consensus.GetStakeDistribution -> PoolDistr StandardCrypto -> Map (Hash StakePoolKey) Rational
fromShelleyPoolDistr result'
PoolDistr StandardCrypto
r'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
era (QueryUTxO QueryUTxOFilter
QueryUTxOWhole) BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
utxo' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
BlockQuery (ShelleyBlock protocol ledgerera) result'
Consensus.GetUTxOWhole -> ShelleyBasedEra era -> UTxO ledgerera -> UTxO era
forall era ledgerera.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
ShelleyBasedEra era -> UTxO ledgerera -> UTxO era
fromLedgerUTxO ShelleyBasedEra era
era result'
UTxO ledgerera
utxo'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
era (QueryUTxO QueryUTxOByAddress{}) BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
utxo' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
Consensus.GetUTxOByAddress{} -> ShelleyBasedEra era -> UTxO ledgerera -> UTxO era
forall era ledgerera.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
ShelleyBasedEra era -> UTxO ledgerera -> UTxO era
fromLedgerUTxO ShelleyBasedEra era
era result'
UTxO ledgerera
utxo'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
era (QueryUTxO QueryUTxOByTxIn{}) BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
utxo' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
Consensus.GetUTxOByTxIn{} -> ShelleyBasedEra era -> UTxO ledgerera -> UTxO era
forall era ledgerera.
(ShelleyLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
ShelleyBasedEra era -> UTxO ledgerera -> UTxO era
fromLedgerUTxO ShelleyBasedEra era
era result'
UTxO ledgerera
utxo'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
_ (QueryStakeAddresses Set StakeCredential
_ NetworkId
nId) BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
r' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
Consensus.GetFilteredDelegationsAndRewardAccounts{}
-> let (Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
delegs, RewardAccounts StandardCrypto
rwaccs) = result'
(Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto),
RewardAccounts StandardCrypto)
r'
in ( (StakeCredential -> StakeAddress)
-> Map StakeCredential Lovelace -> Map StakeAddress Lovelace
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys (NetworkId -> StakeCredential -> StakeAddress
makeStakeAddress NetworkId
nId) (Map StakeCredential Lovelace -> Map StakeAddress Lovelace)
-> Map StakeCredential Lovelace -> Map StakeAddress Lovelace
forall a b. (a -> b) -> a -> b
$ RewardAccounts StandardCrypto -> Map StakeCredential Lovelace
fromShelleyRewardAccounts RewardAccounts StandardCrypto
rwaccs
, (StakeCredential -> StakeAddress)
-> Map StakeCredential (Hash StakePoolKey)
-> Map StakeAddress (Hash StakePoolKey)
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys (NetworkId -> StakeCredential -> StakeAddress
makeStakeAddress NetworkId
nId) (Map StakeCredential (Hash StakePoolKey)
-> Map StakeAddress (Hash StakePoolKey))
-> Map StakeCredential (Hash StakePoolKey)
-> Map StakeAddress (Hash StakePoolKey)
forall a b. (a -> b) -> a -> b
$ Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
-> Map StakeCredential (Hash StakePoolKey)
fromShelleyDelegations Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
delegs
)
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
_ QueryInShelleyBasedEra era result
QueryStakePools BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
poolids' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
BlockQuery (ShelleyBlock protocol ledgerera) result'
Consensus.GetStakePools -> (KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey)
-> Set (KeyHash 'StakePool StandardCrypto)
-> Set (Hash StakePoolKey)
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey
StakePoolKeyHash result'
Set (KeyHash 'StakePool StandardCrypto)
poolids'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
_ QueryStakePoolParameters{} BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
poolparams' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
Consensus.GetStakePoolParams{} -> (PoolParams StandardCrypto -> StakePoolParameters)
-> Map (Hash StakePoolKey) (PoolParams StandardCrypto)
-> Map (Hash StakePoolKey) StakePoolParameters
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map PoolParams StandardCrypto -> StakePoolParameters
fromShelleyPoolParams
(Map (Hash StakePoolKey) (PoolParams StandardCrypto)
-> Map (Hash StakePoolKey) StakePoolParameters)
-> (Map
(KeyHash 'StakePool StandardCrypto) (PoolParams StandardCrypto)
-> Map (Hash StakePoolKey) (PoolParams StandardCrypto))
-> Map
(KeyHash 'StakePool StandardCrypto) (PoolParams StandardCrypto)
-> Map (Hash StakePoolKey) StakePoolParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey)
-> Map
(KeyHash 'StakePool StandardCrypto) (PoolParams StandardCrypto)
-> Map (Hash StakePoolKey) (PoolParams StandardCrypto)
forall k1 k2 a. (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeysMonotonic KeyHash 'StakePool StandardCrypto -> Hash StakePoolKey
StakePoolKeyHash
(Map
(KeyHash 'StakePool StandardCrypto) (PoolParams StandardCrypto)
-> Map (Hash StakePoolKey) StakePoolParameters)
-> Map
(KeyHash 'StakePool StandardCrypto) (PoolParams StandardCrypto)
-> Map (Hash StakePoolKey) StakePoolParameters
forall a b. (a -> b) -> a -> b
$ result'
Map (KeyHash 'StakePool StandardCrypto) (PoolParams StandardCrypto)
poolparams'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
_ QueryDebugLedgerState{} BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
r' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
Consensus.GetCBOR Consensus.DebugNewEpochState -> Serialised (NewEpochState (ShelleyLedgerEra era))
-> SerialisedDebugLedgerState era
forall era.
Serialised (NewEpochState (ShelleyLedgerEra era))
-> SerialisedDebugLedgerState era
SerialisedDebugLedgerState result'
Serialised (NewEpochState (ShelleyLedgerEra era))
r'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
_ QueryInShelleyBasedEra era result
QueryProtocolState BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
r' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
Consensus.GetCBOR Consensus.DebugChainDepState -> Serialised (ChainDepState (ConsensusProtocol era))
-> ProtocolState era
forall era.
Serialised (ChainDepState (ConsensusProtocol era))
-> ProtocolState era
ProtocolState result'
Serialised (ChainDepState (ConsensusProtocol era))
r'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultShelleyBased ShelleyBasedEra era
_ QueryInShelleyBasedEra era result
QueryCurrentEpochState BlockQuery (ShelleyBlock protocol ledgerera) result'
q' result'
r' =
case BlockQuery (ShelleyBlock protocol ledgerera) result'
q' of
Consensus.GetCBOR Consensus.DebugEpochState -> Serialised (EpochState (ShelleyLedgerEra era))
-> SerialisedCurrentEpochState era
forall era.
Serialised (EpochState (ShelleyLedgerEra era))
-> SerialisedCurrentEpochState era
SerialisedCurrentEpochState result'
Serialised (EpochState (ShelleyLedgerEra era))
r'
BlockQuery (ShelleyBlock protocol ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultMismatch :: a
fromConsensusQueryResultMismatch :: a
fromConsensusQueryResultMismatch =
String -> a
forall a. HasCallStack => String -> a
error String
"fromConsensusQueryResult: internal query mismatch"
fromConsensusEraMismatch :: SListI xs
=> Consensus.MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch :: MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch = MismatchEraInfo xs -> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
Consensus.mkEraMismatch