{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DataKinds #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
module Bcc.Api.Query (
QueryInMode(..),
QueryInEra(..),
QueryInSophieBasedEra(..),
QueryUTxOFilter(..),
UTxO(..),
UTxOInAnyEra(..),
toConsensusQuery,
fromConsensusQueryResult,
SerialisedDebugLedgerState(..),
ProtocolState(..),
DebugLedgerState(..),
EraHistory(..),
SystemStart(..),
SlotsInEpoch(..),
SlotsToEpochEnd(..),
slotToEpoch,
LedgerState(..),
getProgress,
toLedgerUTxO,
fromLedgerUTxO,
) where
import Data.Aeson (ToJSON (..), object, (.=))
import Data.Bifunctor (bimap)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe (mapMaybe)
import Data.SOP.Strict (SListI)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Typeable
import Prelude
import Shardagnostic.Network.Protocol.LocalStateQuery.Client (Some (..))
import qualified Shardagnostic.Consensus.HardFork.Combinator as Consensus
import Shardagnostic.Consensus.HardFork.Combinator.AcrossEras (EraMismatch)
import qualified Shardagnostic.Consensus.HardFork.Combinator.AcrossEras as Consensus
import qualified Shardagnostic.Consensus.HardFork.Combinator.Degenerate as Consensus
import qualified Shardagnostic.Consensus.HardFork.History as History
import qualified Shardagnostic.Consensus.HardFork.History.Qry as Qry
import Shardagnostic.Consensus.BlockchainTime.WallClock.Types (RelativeTime, SlotLength)
import qualified Shardagnostic.Consensus.Cole.Ledger as Consensus
import Shardagnostic.Consensus.Bcc.Block (LedgerState (..), StandardCrypto)
import qualified Shardagnostic.Consensus.Bcc.Block as Consensus
import qualified Shardagnostic.Consensus.Ledger.Query as Consensus
import qualified Shardagnostic.Consensus.Sophie.Ledger as Consensus
import Shardagnostic.Network.Block (Serialised)
import Bcc.Binary
import Bcc.Slotting.Time (SystemStart (..))
import qualified Bcc.Chain.Update.Validation.Interface as Cole.Update
import qualified Bcc.Ledger.Core as Core
import qualified Bcc.Ledger.Era as Ledger
import qualified Sophie.Spec.Ledger.API as Sophie
import qualified Sophie.Spec.Ledger.LedgerState as Sophie
import Bcc.Api.Address
import Bcc.Api.Block
import Bcc.Api.Certificate
import Bcc.Api.Eras
import Bcc.Api.GenesisParameters
import Bcc.Api.KeysSophie
import Bcc.Api.Modes
import Bcc.Api.NetworkId
import Bcc.Api.Orphans ()
import Bcc.Api.ProtocolParameters
import Bcc.Api.TxBody
import Bcc.Api.Value
import Data.Word (Word64)
data QueryInMode mode result where
QueryCurrentEra
:: ConsensusModeIsMultiEra mode
-> QueryInMode mode AnyBccEra
QueryInEra
:: EraInMode era mode
-> QueryInEra era result
-> QueryInMode mode (Either EraMismatch result)
QueryEraHistory
:: ConsensusModeIsMultiEra mode
-> QueryInMode mode (EraHistory mode)
QuerySystemStart
:: QueryInMode mode SystemStart
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
QueryColeUpdateState :: QueryInEra ColeEra ColeUpdateState
QueryInSophieBasedEra :: SophieBasedEra era
-> QueryInSophieBasedEra era result
-> QueryInEra era result
deriving instance Show (QueryInEra era result)
data QueryInSophieBasedEra era result where
QueryChainPoint
:: QueryInSophieBasedEra era ChainPoint
QueryEpoch
:: QueryInSophieBasedEra era EpochNo
QueryGenesisParameters
:: QueryInSophieBasedEra era GenesisParameters
QueryProtocolParameters
:: QueryInSophieBasedEra era ProtocolParameters
QueryProtocolParametersUpdate
:: QueryInSophieBasedEra era
(Map (Hash GenesisKey) ProtocolParametersUpdate)
QueryStakeDistribution
:: QueryInSophieBasedEra era (Map (Hash StakePoolKey) Rational)
QueryUTxO
:: QueryUTxOFilter
-> QueryInSophieBasedEra era (UTxO era)
QueryStakeAddresses
:: Set StakeCredential
-> NetworkId
-> QueryInSophieBasedEra era (Map StakeAddress Entropic,
Map StakeAddress PoolId)
QueryStakePools
:: QueryInSophieBasedEra era (Set PoolId)
QueryStakePoolParameters
:: Set PoolId
-> QueryInSophieBasedEra era (Map PoolId StakePoolParameters)
QueryDebugLedgerState
:: QueryInSophieBasedEra era (SerialisedDebugLedgerState era)
QueryProtocolState
:: QueryInSophieBasedEra era (ProtocolState era)
deriving instance Show (QueryInSophieBasedEra 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 ColeUpdateState = ColeUpdateState Cole.Update.State
deriving Int -> ColeUpdateState -> ShowS
[ColeUpdateState] -> ShowS
ColeUpdateState -> String
(Int -> ColeUpdateState -> ShowS)
-> (ColeUpdateState -> String)
-> ([ColeUpdateState] -> ShowS)
-> Show ColeUpdateState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColeUpdateState] -> ShowS
$cshowList :: [ColeUpdateState] -> ShowS
show :: ColeUpdateState -> String
$cshow :: ColeUpdateState -> String
showsPrec :: Int -> ColeUpdateState -> ShowS
$cshowsPrec :: Int -> ColeUpdateState -> ShowS
Show
newtype UTxO era = UTxO (Map TxIn (TxOut 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)
data UTxOInAnyEra where
UTxOInAnyEra :: BccEra era
-> UTxO era
-> UTxOInAnyEra
deriving instance Show UTxOInAnyEra
instance IsBccEra era => ToJSON (UTxO era) where
toJSON :: UTxO era -> Value
toJSON (UTxO Map TxIn (TxOut era)
m) = Map TxIn (TxOut era) -> Value
forall a. ToJSON a => a -> Value
toJSON Map TxIn (TxOut era)
m
newtype SerialisedDebugLedgerState era
= SerialisedDebugLedgerState (Serialised (Sophie.NewEpochState (SophieLedgerEra era)))
data DebugLedgerState era where
DebugLedgerState :: SophieLedgerEra era ~ ledgerera => Sophie.NewEpochState ledgerera -> DebugLedgerState era
instance (Typeable era, Sophie.TransLedgerState FromCBOR (SophieLedgerEra era)) => FromCBOR (DebugLedgerState era) where
fromCBOR :: Decoder s (DebugLedgerState era)
fromCBOR = NewEpochState (SophieLedgerEra era) -> DebugLedgerState era
forall era ledgerera.
(SophieLedgerEra era ~ ledgerera) =>
NewEpochState ledgerera -> DebugLedgerState era
DebugLedgerState (NewEpochState (SophieLedgerEra era) -> DebugLedgerState era)
-> Decoder s (NewEpochState (SophieLedgerEra era))
-> Decoder s (DebugLedgerState era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall s. Decoder s (NewEpochState (SophieLedgerEra era))
forall a s. FromCBOR a => Decoder s a
fromCBOR :: Decoder s (Sophie.NewEpochState (SophieLedgerEra era)))
instance ( IsSophieBasedEra era
, SophieLedgerEra era ~ ledgerera
, Consensus.SophieBasedEra ledgerera
, ToJSON (Core.PParams ledgerera)
, ToJSON (Core.PParamsDelta ledgerera)
, ToJSON (Core.TxOut ledgerera)) => ToJSON (DebugLedgerState era) where
toJSON :: DebugLedgerState era -> Value
toJSON (DebugLedgerState NewEpochState ledgerera
newEpochS) = [Pair] -> Value
object [ Text
"lastEpoch" Text -> EpochNo -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= NewEpochState ledgerera -> EpochNo
forall era. NewEpochState era -> EpochNo
Sophie.nesEL NewEpochState ledgerera
newEpochS
, Text
"blocksBefore" Text -> BlocksMade (Crypto ledgerera) -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= NewEpochState ledgerera -> BlocksMade (Crypto ledgerera)
forall era. NewEpochState era -> BlocksMade (Crypto era)
Sophie.nesBprev NewEpochState ledgerera
newEpochS
, Text
"blocksCurrent" Text -> BlocksMade (Crypto ledgerera) -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= NewEpochState ledgerera -> BlocksMade (Crypto ledgerera)
forall era. NewEpochState era -> BlocksMade (Crypto era)
Sophie.nesBcur NewEpochState ledgerera
newEpochS
, Text
"stateBefore" Text -> EpochState ledgerera -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= NewEpochState ledgerera -> EpochState ledgerera
forall era. NewEpochState era -> EpochState era
Sophie.nesEs NewEpochState ledgerera
newEpochS
, Text
"possibleRewardUpdate" Text -> StrictMaybe (PulsingRewUpdate (Crypto ledgerera)) -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= NewEpochState ledgerera
-> StrictMaybe (PulsingRewUpdate (Crypto ledgerera))
forall era.
NewEpochState era -> StrictMaybe (PulsingRewUpdate (Crypto era))
Sophie.nesRu NewEpochState ledgerera
newEpochS
, Text
"stakeDistrib" Text -> PoolDistr (Crypto ledgerera) -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= NewEpochState ledgerera -> PoolDistr (Crypto ledgerera)
forall era. NewEpochState era -> PoolDistr (Crypto era)
Sophie.nesPd NewEpochState ledgerera
newEpochS
]
newtype ProtocolState era
= ProtocolState (Serialised (Sophie.ChainDepState (Ledger.Crypto (SophieLedgerEra era))))
toSophieAddrSet :: BccEra era
-> Set AddressAny
-> Set (Sophie.Addr Consensus.StandardCrypto)
toSophieAddrSet :: BccEra era -> Set AddressAny -> Set (Addr StandardCrypto)
toSophieAddrSet BccEra 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
toSophieAddr
([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 (BccEra era -> AddressAny -> Maybe (AddressInEra era)
forall era. BccEra era -> AddressAny -> Maybe (AddressInEra era)
anyAddressInEra BccEra 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 :: SophieLedgerEra era ~ ledgerera
=> Ledger.Crypto ledgerera ~ StandardCrypto
=> SophieBasedEra era
-> UTxO era
-> Sophie.UTxO ledgerera
toLedgerUTxO :: SophieBasedEra era -> UTxO era -> UTxO ledgerera
toLedgerUTxO SophieBasedEra era
era (UTxO Map TxIn (TxOut era)
utxo) =
Map (TxIn StandardCrypto) (TxOut ledgerera) -> UTxO ledgerera
forall era. Map (TxIn (Crypto era)) (TxOut era) -> UTxO era
Sophie.UTxO
(Map (TxIn StandardCrypto) (TxOut ledgerera) -> UTxO ledgerera)
-> (Map TxIn (TxOut era)
-> Map (TxIn StandardCrypto) (TxOut ledgerera))
-> Map TxIn (TxOut 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 era)
-> [(TxIn StandardCrypto, TxOut ledgerera)])
-> Map TxIn (TxOut era)
-> Map (TxIn StandardCrypto) (TxOut ledgerera)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TxIn, TxOut era) -> (TxIn StandardCrypto, TxOut ledgerera))
-> [(TxIn, TxOut era)] -> [(TxIn StandardCrypto, TxOut ledgerera)]
forall a b. (a -> b) -> [a] -> [b]
map ((TxIn -> TxIn StandardCrypto)
-> (TxOut era -> TxOut ledgerera)
-> (TxIn, TxOut 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
toSophieTxIn (SophieBasedEra era -> TxOut era -> TxOut ledgerera
forall era ledgerera.
(SophieLedgerEra era ~ ledgerera) =>
SophieBasedEra era -> TxOut era -> TxOut ledgerera
toSophieTxOut SophieBasedEra era
era))
([(TxIn, TxOut era)] -> [(TxIn StandardCrypto, TxOut ledgerera)])
-> (Map TxIn (TxOut era) -> [(TxIn, TxOut era)])
-> Map TxIn (TxOut era)
-> [(TxIn StandardCrypto, TxOut ledgerera)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map TxIn (TxOut era) -> [(TxIn, TxOut era)]
forall k a. Map k a -> [(k, a)]
Map.toList
(Map TxIn (TxOut era) -> UTxO ledgerera)
-> Map TxIn (TxOut era) -> UTxO ledgerera
forall a b. (a -> b) -> a -> b
$ Map TxIn (TxOut era)
utxo
fromLedgerUTxO :: SophieLedgerEra era ~ ledgerera
=> Ledger.Crypto ledgerera ~ StandardCrypto
=> SophieBasedEra era
-> Sophie.UTxO ledgerera
-> UTxO era
fromLedgerUTxO :: SophieBasedEra era -> UTxO ledgerera -> UTxO era
fromLedgerUTxO SophieBasedEra era
era (Sophie.UTxO Map (TxIn (Crypto ledgerera)) (TxOut ledgerera)
utxo) =
Map TxIn (TxOut era) -> UTxO era
forall era. Map TxIn (TxOut era) -> UTxO era
UTxO
(Map TxIn (TxOut era) -> UTxO era)
-> (Map (TxIn StandardCrypto) (TxOut ledgerera)
-> Map TxIn (TxOut era))
-> Map (TxIn StandardCrypto) (TxOut ledgerera)
-> UTxO era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(TxIn, TxOut era)] -> Map TxIn (TxOut era)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
([(TxIn, TxOut era)] -> Map TxIn (TxOut era))
-> (Map (TxIn StandardCrypto) (TxOut ledgerera)
-> [(TxIn, TxOut era)])
-> Map (TxIn StandardCrypto) (TxOut ledgerera)
-> Map TxIn (TxOut era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((TxIn StandardCrypto, TxOut ledgerera) -> (TxIn, TxOut era))
-> [(TxIn StandardCrypto, TxOut ledgerera)] -> [(TxIn, TxOut era)]
forall a b. (a -> b) -> [a] -> [b]
map ((TxIn StandardCrypto -> TxIn)
-> (TxOut ledgerera -> TxOut era)
-> (TxIn StandardCrypto, TxOut ledgerera)
-> (TxIn, TxOut era)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap TxIn StandardCrypto -> TxIn
fromSophieTxIn (SophieBasedEra era -> TxOut ledgerera -> TxOut era
forall era ledgerera.
(SophieLedgerEra era ~ ledgerera) =>
SophieBasedEra era -> TxOut ledgerera -> TxOut era
fromSophieTxOut SophieBasedEra era
era))
([(TxIn StandardCrypto, TxOut ledgerera)] -> [(TxIn, TxOut era)])
-> (Map (TxIn StandardCrypto) (TxOut ledgerera)
-> [(TxIn StandardCrypto, TxOut ledgerera)])
-> Map (TxIn StandardCrypto) (TxOut ledgerera)
-> [(TxIn, TxOut 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
fromSophiePoolDistr :: Sophie.PoolDistr StandardCrypto
-> Map (Hash StakePoolKey) Rational
fromSophiePoolDistr :: PoolDistr StandardCrypto -> Map (Hash StakePoolKey) Rational
fromSophiePoolDistr =
[(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
Sophie.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)
Sophie.unPoolDistr
fromSophieDelegations :: Map (Sophie.Credential Sophie.Staking StandardCrypto)
(Sophie.KeyHash Sophie.StakePool StandardCrypto)
-> Map StakeCredential PoolId
fromSophieDelegations :: Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
-> Map StakeCredential (Hash StakePoolKey)
fromSophieDelegations =
[(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
fromSophieStakeCredential 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
fromSophieRewardAccounts :: Sophie.RewardAccounts Consensus.StandardCrypto
-> Map StakeCredential Entropic
fromSophieRewardAccounts :: RewardAccounts StandardCrypto -> Map StakeCredential Entropic
fromSophieRewardAccounts =
[(StakeCredential, Entropic)] -> Map StakeCredential Entropic
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
([(StakeCredential, Entropic)] -> Map StakeCredential Entropic)
-> (RewardAccounts StandardCrypto -> [(StakeCredential, Entropic)])
-> RewardAccounts StandardCrypto
-> Map StakeCredential Entropic
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Credential 'Staking StandardCrypto, Coin)
-> (StakeCredential, Entropic))
-> [(Credential 'Staking StandardCrypto, Coin)]
-> [(StakeCredential, Entropic)]
forall a b. (a -> b) -> [a] -> [b]
map ((Credential 'Staking StandardCrypto -> StakeCredential)
-> (Coin -> Entropic)
-> (Credential 'Staking StandardCrypto, Coin)
-> (StakeCredential, Entropic)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Credential 'Staking StandardCrypto -> StakeCredential
fromSophieStakeCredential Coin -> Entropic
fromSophieEntropic)
([(Credential 'Staking StandardCrypto, Coin)]
-> [(StakeCredential, Entropic)])
-> (RewardAccounts StandardCrypto
-> [(Credential 'Staking StandardCrypto, Coin)])
-> RewardAccounts StandardCrypto
-> [(StakeCredential, Entropic)]
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
BccModeIsMultiEra) =
Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Some
(Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]))
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Some
(Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])))
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Some
(Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
forall blk result. BlockQuery blk result -> Query blk result
Consensus.BlockQuery (BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]))
-> BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
forall a b. (a -> b) -> a -> b
$
QueryHardFork
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
forall (xs1 :: [*]) x a.
IsNonEmpty xs1 =>
QueryHardFork (x : xs1) a -> BlockQuery (HardForkBlock (x : xs1)) a
Consensus.QueryHardFork
QueryHardFork
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
(EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
forall (xs :: [*]). QueryHardFork xs (EraIndex xs)
Consensus.GetCurrentEra
toConsensusQuery (QueryInEra EraInMode era mode
ColeEraInColeMode QueryInEra era result
QueryColeUpdateState) =
Query
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State)
-> Some (Query (HardForkBlock '[ColeBlock]))
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (Query
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State)
-> Some (Query (HardForkBlock '[ColeBlock])))
-> Query
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State)
-> Some (Query (HardForkBlock '[ColeBlock]))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State)
-> Query
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State)
forall blk result. BlockQuery blk result -> Query blk result
Consensus.BlockQuery (BlockQuery
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State)
-> Query
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State))
-> BlockQuery
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State)
-> Query
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State)
forall a b. (a -> b) -> a -> b
$
BlockQuery ColeBlock State
-> BlockQuery
(HardForkBlock '[ColeBlock])
(HardForkQueryResult '[ColeBlock] State)
forall b a result.
(HardForkQueryResult '[b] result ~ a) =>
BlockQuery b result -> BlockQuery (HardForkBlock '[b]) a
Consensus.DegenQuery
BlockQuery ColeBlock State
Consensus.GetUpdateInterfaceState
toConsensusQuery (QueryEraHistory ConsensusModeIsMultiEra mode
BccModeIsMultiEra) =
Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Some
(Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]))
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Some
(Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])))
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Some
(Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
forall blk result. BlockQuery blk result -> Query blk result
Consensus.BlockQuery (BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]))
-> BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
forall a b. (a -> b) -> a -> b
$
QueryHardFork
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
-> BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
forall (xs1 :: [*]) x a.
IsNonEmpty xs1 =>
QueryHardFork (x : xs1) a -> BlockQuery (HardForkBlock (x : xs1)) a
Consensus.QueryHardFork
QueryHardFork
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
(Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra 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 (QueryInEra EraInMode era mode
ColeEraInBccMode QueryInEra era result
QueryColeUpdateState) =
Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State)
-> Some
(Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]))
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State)
-> Some
(Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])))
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State)
-> Some
(Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]))
forall a b. (a -> b) -> a -> b
$ BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State)
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State)
forall blk result. BlockQuery blk result -> Query blk result
Consensus.BlockQuery (BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State)
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State))
-> BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State)
-> Query
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State)
forall a b. (a -> b) -> a -> b
$
BlockQuery ColeBlock State
-> BlockQuery
(HardForkBlock
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
(BccQueryResult StandardCrypto State)
forall c a result.
(BccQueryResult c result ~ a) =>
BlockQuery ColeBlock result -> BccQuery c a
Consensus.QueryIfCurrentCole
BlockQuery ColeBlock State
Consensus.GetUpdateInterfaceState
toConsensusQuery (QueryInEra EraInMode era mode
erainmode (QueryInSophieBasedEra SophieBasedEra era
era QueryInSophieBasedEra era result
q)) =
case EraInMode era mode
erainmode of
EraInMode era mode
ColeEraInColeMode -> case SophieBasedEra era
era of {}
EraInMode era mode
SophieEraInSophieMode -> EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
forall era ledgerera mode block (xs :: [*]) result.
(ConsensusBlockForEra era ~ SophieBlock ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra era result
q
EraInMode era mode
ColeEraInBccMode -> case SophieBasedEra era
era of {}
EraInMode era mode
SophieEraInBccMode -> EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
forall era ledgerera mode block (xs :: [*]) result.
(ConsensusBlockForEra era ~ SophieBlock ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra era result
q
EraInMode era mode
EvieEraInBccMode -> EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
forall era ledgerera mode block (xs :: [*]) result.
(ConsensusBlockForEra era ~ SophieBlock ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra era result
q
EraInMode era mode
JenEraInBccMode -> EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
forall era ledgerera mode block (xs :: [*]) result.
(ConsensusBlockForEra era ~ SophieBlock ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra era result
q
EraInMode era mode
AurumEraInBccMode -> EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
forall era ledgerera mode block (xs :: [*]) result.
(ConsensusBlockForEra era ~ SophieBlock ledgerera,
Crypto ledgerera ~ StandardCrypto,
ConsensusBlockForMode mode ~ block, block ~ HardForkBlock xs) =>
EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra era result
q
toConsensusQuerySophieBased
:: forall era ledgerera mode block xs result.
ConsensusBlockForEra era ~ Consensus.SophieBlock ledgerera
=> Ledger.Crypto ledgerera ~ Consensus.StandardCrypto
=> ConsensusBlockForMode mode ~ block
=> block ~ Consensus.HardForkBlock xs
=> EraInMode era mode
-> QueryInSophieBasedEra era result
-> Some (Consensus.Query block)
toConsensusQuerySophieBased :: EraInMode era mode
-> QueryInSophieBasedEra era result -> Some (Query block)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra era result
QueryChainPoint =
Query
block (HardForkQueryResult xs (Point (SophieBlock ledgerera)))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(SophieBlock ledgerera) (Point (SophieBlock ledgerera))
-> Query
block (HardForkQueryResult xs (Point (SophieBlock 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 (SophieBlock ledgerera) (Point (SophieBlock ledgerera))
forall era. BlockQuery (SophieBlock era) (Point (SophieBlock era))
Consensus.GetLedgerTip)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra 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 (SophieBlock 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 (SophieBlock ledgerera) EpochNo
forall era. BlockQuery (SophieBlock era) EpochNo
Consensus.GetEpochNo)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra 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 (SophieBlock 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 (SophieBlock ledgerera) (CompactGenesis ledgerera)
forall era. BlockQuery (SophieBlock era) (CompactGenesis era)
Consensus.GetGenesisConfig)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra 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 (SophieBlock 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 (SophieBlock ledgerera) (PParams ledgerera)
forall era. BlockQuery (SophieBlock era) (PParams era)
Consensus.GetCurrentPParams)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra 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 (SophieBlock 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 (SophieBlock ledgerera) (ProposedPPUpdates ledgerera)
forall era. BlockQuery (SophieBlock era) (ProposedPPUpdates era)
Consensus.GetProposedPParamsUpdates)
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra 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 (SophieBlock 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 (SophieBlock ledgerera) (PoolDistr StandardCrypto)
forall era.
BlockQuery (SophieBlock era) (PoolDistr (EraCrypto era))
Consensus.GetStakeDistribution)
toConsensusQuerySophieBased 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 (SophieBlock 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 (SophieBlock ledgerera) (UTxO ledgerera)
forall era. BlockQuery (SophieBlock era) (UTxO era)
Consensus.GetUTxOWhole)
toConsensusQuerySophieBased 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 (SophieBlock 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 (SophieBlock ledgerera) (UTxO ledgerera)
forall era.
Set (Addr (EraCrypto era))
-> BlockQuery (SophieBlock era) (UTxO era)
Consensus.GetUTxOByAddress Set (Addr StandardCrypto)
Set (Addr (EraCrypto ledgerera))
addrs'))
where
addrs' :: Set (Sophie.Addr Consensus.StandardCrypto)
addrs' :: Set (Addr StandardCrypto)
addrs' = BccEra era -> Set AddressAny -> Set (Addr StandardCrypto)
forall era.
BccEra era -> Set AddressAny -> Set (Addr StandardCrypto)
toSophieAddrSet (EraInMode era mode -> BccEra era
forall era mode. EraInMode era mode -> BccEra era
eraInModeToEra EraInMode era mode
erainmode) Set AddressAny
addrs
toConsensusQuerySophieBased 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 (SophieBlock 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 (SophieBlock ledgerera) (UTxO ledgerera)
forall era.
Set (TxIn (EraCrypto era))
-> BlockQuery (SophieBlock era) (UTxO era)
Consensus.GetUTxOByTxIn Set (TxIn StandardCrypto)
Set (TxIn (EraCrypto ledgerera))
txins'))
where
txins' :: Set (Sophie.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
toSophieTxIn Set TxIn
txins
toConsensusQuerySophieBased 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
(SophieBlock 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
(SophieBlock ledgerera)
(Delegations (EraCrypto ledgerera),
RewardAccounts (EraCrypto ledgerera))
forall era.
Set (Credential 'Staking (EraCrypto era))
-> BlockQuery
(SophieBlock era)
(Delegations (EraCrypto era), RewardAccounts (EraCrypto era))
Consensus.GetFilteredDelegationsAndRewardAccounts Set (Credential 'Staking StandardCrypto)
Set (Credential 'Staking (EraCrypto ledgerera))
creds'))
where
creds' :: Set (Sophie.Credential Sophie.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
toSophieStakeCredential Set StakeCredential
creds
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra 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
(SophieBlock 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
(SophieBlock ledgerera) (Set (KeyHash 'StakePool StandardCrypto))
forall era.
BlockQuery
(SophieBlock era) (Set (KeyHash 'StakePool (EraCrypto era)))
Consensus.GetStakePools)
toConsensusQuerySophieBased 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
(SophieBlock 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
(SophieBlock ledgerera)
(Map
(KeyHash 'StakePool (EraCrypto ledgerera))
(PoolParams (EraCrypto ledgerera)))
forall era.
Set (KeyHash 'StakePool (EraCrypto era))
-> BlockQuery
(SophieBlock era)
(Map
(KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era)))
Consensus.GetStakePoolParams Set (KeyHash 'StakePool StandardCrypto)
Set (KeyHash 'StakePool (EraCrypto ledgerera))
poolids'))
where
poolids' :: Set (Sophie.KeyHash Sophie.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
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra 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
(SophieBlock 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 (SophieBlock ledgerera) (NewEpochState ledgerera)
-> BlockQuery
(SophieBlock ledgerera) (Serialised (NewEpochState ledgerera))
forall era result.
BlockQuery (SophieBlock era) result
-> BlockQuery (SophieBlock era) (Serialised result)
Consensus.GetCBOR BlockQuery (SophieBlock ledgerera) (NewEpochState ledgerera)
forall era. BlockQuery (SophieBlock era) (NewEpochState era)
Consensus.DebugNewEpochState))
toConsensusQuerySophieBased EraInMode era mode
erainmode QueryInSophieBasedEra era result
QueryProtocolState =
Query
block
(HardForkQueryResult
xs (Serialised (ChainDepState StandardCrypto)))
-> Some (Query block)
forall k (f :: k -> *) (a :: k). f a -> Some f
Some (EraInMode era mode
-> BlockQuery
(SophieBlock ledgerera) (Serialised (ChainDepState StandardCrypto))
-> Query
block
(HardForkQueryResult
xs (Serialised (ChainDepState 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 (SophieBlock ledgerera) (ChainDepState StandardCrypto)
-> BlockQuery
(SophieBlock ledgerera) (Serialised (ChainDepState StandardCrypto))
forall era result.
BlockQuery (SophieBlock era) result
-> BlockQuery (SophieBlock era) (Serialised result)
Consensus.GetCBOR BlockQuery (SophieBlock ledgerera) (ChainDepState StandardCrypto)
forall era.
BlockQuery (SophieBlock era) (ChainDepState (EraCrypto era))
Consensus.DebugChainDepState))
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
ColeEraInColeMode -> 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
SophieEraInSophieMode -> 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
ColeEraInBccMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(BccQueryResult c result ~ a) =>
BlockQuery ColeBlock result -> BccQuery c a
Consensus.QueryIfCurrentCole
EraInMode era mode
SophieEraInBccMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(BccQueryResult c result ~ a) =>
BlockQuery (SophieBlock (SophieEra c)) result -> BccQuery c a
Consensus.QueryIfCurrentSophie
EraInMode era mode
EvieEraInBccMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(BccQueryResult c result ~ a) =>
BlockQuery (SophieBlock (EvieEra c)) result -> BccQuery c a
Consensus.QueryIfCurrentEvie
EraInMode era mode
JenEraInBccMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(BccQueryResult c result ~ a) =>
BlockQuery (SophieBlock (JenEra c)) result -> BccQuery c a
Consensus.QueryIfCurrentJen
EraInMode era mode
AurumEraInBccMode -> BlockQuery erablock result -> BlockQuery modeblock result'
forall c a result.
(BccQueryResult c result ~ a) =>
BlockQuery (SophieBlock (AurumEra c)) result -> BccQuery c a
Consensus.QueryIfCurrentAurum
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
BccModeIsMultiEra) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryHardFork Consensus.GetInterpreter)
-> ConsensusMode BccMode
-> Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraHistory BccMode
forall mode (xs :: [*]).
(ConsensusBlockForMode mode ~ HardForkBlock xs) =>
ConsensusMode mode -> Interpreter xs -> EraHistory mode
EraHistory ConsensusMode BccMode
BccMode result'
Interpreter
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra 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 (QueryCurrentEra ConsensusModeIsMultiEra mode
BccModeIsMultiEra) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryHardFork Consensus.GetCurrentEra)
-> AnyEraInMode BccMode -> AnyBccEra
forall mode. AnyEraInMode mode -> AnyBccEra
anyEraInModeToAnyEra (ConsensusMode BccMode
-> EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> AnyEraInMode BccMode
forall mode (xs :: [*]).
(ConsensusBlockForMode mode ~ HardForkBlock xs) =>
ConsensusMode mode -> EraIndex xs -> AnyEraInMode mode
fromConsensusEraIndex ConsensusMode BccMode
BccMode result'
EraIndex
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
r')
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
ColeEraInColeMode
QueryInEra era result
QueryColeUpdateState) Query block result'
q' result'
r' =
case (Query block result'
q', result'
r') of
(Consensus.BlockQuery (Consensus.DegenQuery Consensus.GetUpdateInterfaceState),
Consensus.DegenQueryResult r'')
-> ColeUpdateState -> Either EraMismatch ColeUpdateState
forall a b. b -> Either a b
Right (State -> ColeUpdateState
ColeUpdateState State
r'')
(Query block result', result')
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
ColeEraInBccMode
QueryInEra era result
QueryColeUpdateState) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery
(Consensus.QueryIfCurrentCole Consensus.GetUpdateInterfaceState)
-> (MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch)
-> (State -> ColeUpdateState)
-> BccQueryResult StandardCrypto State
-> Either EraMismatch ColeUpdateState
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch State -> ColeUpdateState
ColeUpdateState result'
BccQueryResult StandardCrypto State
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
ColeEraInColeMode
(QueryInSophieBasedEra SophieBasedEra era
era QueryInSophieBasedEra era result
_)) Query block result'
_ result'
_ =
case SophieBasedEra era
era of {}
fromConsensusQueryResult (QueryInEra EraInMode era mode
SophieEraInSophieMode
(QueryInSophieBasedEra SophieBasedEra era
_era QueryInSophieBasedEra 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 (SophieBasedEra SophieEra
-> QueryInSophieBasedEra SophieEra result
-> BlockQuery (SophieBlock (SophieEra StandardCrypto)) result
-> result
-> result
forall era ledgerera result result'.
(SophieLedgerEra era ~ ledgerera, SophieBasedEra ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
SophieBasedEra era
-> QueryInSophieBasedEra era result
-> BlockQuery (SophieBlock ledgerera) result'
-> result'
-> result
fromConsensusQueryResultSophieBased
SophieBasedEra SophieEra
SophieBasedEraSophie QueryInSophieBasedEra era result
QueryInSophieBasedEra SophieEra result
q BlockQuery (SophieBlock (SophieEra StandardCrypto)) result
q'' result
r'')
(Query block result', result')
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
ColeEraInBccMode
(QueryInSophieBasedEra SophieBasedEra era
era QueryInSophieBasedEra era result
_)) Query block result'
_ result'
_ =
case SophieBasedEra era
era of {}
fromConsensusQueryResult (QueryInEra EraInMode era mode
SophieEraInBccMode
(QueryInSophieBasedEra SophieBasedEra era
_era QueryInSophieBasedEra era result
q)) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryIfCurrentSophie q'')
-> (MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch)
-> (result -> result)
-> Either
(MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra 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
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch
(SophieBasedEra SophieEra
-> QueryInSophieBasedEra SophieEra result
-> BlockQuery (SophieBlock (SophieEra StandardCrypto)) result
-> result
-> result
forall era ledgerera result result'.
(SophieLedgerEra era ~ ledgerera, SophieBasedEra ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
SophieBasedEra era
-> QueryInSophieBasedEra era result
-> BlockQuery (SophieBlock ledgerera) result'
-> result'
-> result
fromConsensusQueryResultSophieBased
SophieBasedEra SophieEra
SophieBasedEraSophie QueryInSophieBasedEra era result
QueryInSophieBasedEra SophieEra result
q BlockQuery (SophieBlock (SophieEra StandardCrypto)) result
q'')
result'
Either
(MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
result
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
EvieEraInBccMode
(QueryInSophieBasedEra SophieBasedEra era
_era QueryInSophieBasedEra era result
q)) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryIfCurrentEvie q'')
-> (MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch)
-> (result -> result)
-> Either
(MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra 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
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch
(SophieBasedEra EvieEra
-> QueryInSophieBasedEra EvieEra result
-> BlockQuery (SophieBlock (EvieEra StandardCrypto)) result
-> result
-> result
forall era ledgerera result result'.
(SophieLedgerEra era ~ ledgerera, SophieBasedEra ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
SophieBasedEra era
-> QueryInSophieBasedEra era result
-> BlockQuery (SophieBlock ledgerera) result'
-> result'
-> result
fromConsensusQueryResultSophieBased
SophieBasedEra EvieEra
SophieBasedEraEvie QueryInSophieBasedEra era result
QueryInSophieBasedEra EvieEra result
q BlockQuery (SophieBlock (EvieEra StandardCrypto)) result
q'')
result'
Either
(MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
result
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
JenEraInBccMode
(QueryInSophieBasedEra SophieBasedEra era
_era QueryInSophieBasedEra era result
q)) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryIfCurrentJen q'')
-> (MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch)
-> (result -> result)
-> Either
(MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra 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
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch
(SophieBasedEra JenEra
-> QueryInSophieBasedEra JenEra result
-> BlockQuery (SophieBlock (JenEra StandardCrypto)) result
-> result
-> result
forall era ledgerera result result'.
(SophieLedgerEra era ~ ledgerera, SophieBasedEra ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
SophieBasedEra era
-> QueryInSophieBasedEra era result
-> BlockQuery (SophieBlock ledgerera) result'
-> result'
-> result
fromConsensusQueryResultSophieBased
SophieBasedEra JenEra
SophieBasedEraJen QueryInSophieBasedEra era result
QueryInSophieBasedEra JenEra result
q BlockQuery (SophieBlock (JenEra StandardCrypto)) result
q'')
result'
Either
(MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
result
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResult (QueryInEra EraInMode era mode
AurumEraInBccMode
(QueryInSophieBasedEra SophieBasedEra era
_era QueryInSophieBasedEra era result
q)) Query block result'
q' result'
r' =
case Query block result'
q' of
Consensus.BlockQuery (Consensus.QueryIfCurrentAurum q'')
-> (MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch)
-> (result -> result)
-> Either
(MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra 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
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)]
-> EraMismatch
forall (xs :: [*]). SListI xs => MismatchEraInfo xs -> EraMismatch
fromConsensusEraMismatch
(SophieBasedEra AurumEra
-> QueryInSophieBasedEra AurumEra result
-> BlockQuery (SophieBlock (AurumEra StandardCrypto)) result
-> result
-> result
forall era ledgerera result result'.
(SophieLedgerEra era ~ ledgerera, SophieBasedEra ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
SophieBasedEra era
-> QueryInSophieBasedEra era result
-> BlockQuery (SophieBlock ledgerera) result'
-> result'
-> result
fromConsensusQueryResultSophieBased
SophieBasedEra AurumEra
SophieBasedEraAurum QueryInSophieBasedEra era result
QueryInSophieBasedEra AurumEra result
q BlockQuery (SophieBlock (AurumEra StandardCrypto)) result
q'')
result'
Either
(MismatchEraInfo
'[ColeBlock, SophieBlock (SophieEra StandardCrypto),
SophieBlock (EvieEra StandardCrypto),
SophieBlock (JenEra StandardCrypto),
SophieBlock (AurumEra StandardCrypto)])
result
r'
Query block result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased
:: forall era ledgerera result result'.
SophieLedgerEra era ~ ledgerera
=> Consensus.SophieBasedEra ledgerera
=> Ledger.Crypto ledgerera ~ Consensus.StandardCrypto
=> SophieBasedEra era
-> QueryInSophieBasedEra era result
-> Consensus.BlockQuery (Consensus.SophieBlock ledgerera) result'
-> result'
-> result
fromConsensusQueryResultSophieBased :: SophieBasedEra era
-> QueryInSophieBasedEra era result
-> BlockQuery (SophieBlock ledgerera) result'
-> result'
-> result
fromConsensusQueryResultSophieBased SophieBasedEra era
_ QueryInSophieBasedEra era result
QueryChainPoint BlockQuery (SophieBlock ledgerera) result'
q' result'
point =
case BlockQuery (SophieBlock ledgerera) result'
q' of
BlockQuery (SophieBlock ledgerera) result'
Consensus.GetLedgerTip -> Point (SophieBlock ledgerera) -> ChainPoint
forall ledgerera.
SophieBasedEra ledgerera =>
Point (SophieBlock ledgerera) -> ChainPoint
fromConsensusPoint result'
Point (SophieBlock ledgerera)
point
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
_ QueryInSophieBasedEra era result
QueryEpoch BlockQuery (SophieBlock ledgerera) result'
q' result'
epoch =
case BlockQuery (SophieBlock ledgerera) result'
q' of
BlockQuery (SophieBlock ledgerera) result'
Consensus.GetEpochNo -> result
result'
epoch
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
_ QueryInSophieBasedEra era result
QueryGenesisParameters BlockQuery (SophieBlock ledgerera) result'
q' result'
r' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
BlockQuery (SophieBlock ledgerera) result'
Consensus.GetGenesisConfig -> SophieGenesis ledgerera -> GenesisParameters
forall era. SophieGenesis era -> GenesisParameters
fromSophieGenesis
(CompactGenesis ledgerera -> SophieGenesis ledgerera
forall era. CompactGenesis era -> SophieGenesis era
Consensus.getCompactGenesis result'
CompactGenesis ledgerera
r')
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
era QueryInSophieBasedEra era result
QueryProtocolParameters BlockQuery (SophieBlock ledgerera) result'
q' result'
r' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
BlockQuery (SophieBlock ledgerera) result'
Consensus.GetCurrentPParams -> SophieBasedEra era
-> PParams (SophieLedgerEra era) -> ProtocolParameters
forall era.
SophieBasedEra era
-> PParams (SophieLedgerEra era) -> ProtocolParameters
fromLedgerPParams SophieBasedEra era
era result'
PParams (SophieLedgerEra era)
r'
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
era QueryInSophieBasedEra era result
QueryProtocolParametersUpdate BlockQuery (SophieBlock ledgerera) result'
q' result'
r' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
BlockQuery (SophieBlock ledgerera) result'
Consensus.GetProposedPParamsUpdates -> SophieBasedEra era
-> ProposedPPUpdates ledgerera
-> Map (Hash GenesisKey) ProtocolParametersUpdate
forall era ledgerera.
(SophieLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
SophieBasedEra era
-> ProposedPPUpdates ledgerera
-> Map (Hash GenesisKey) ProtocolParametersUpdate
fromLedgerProposedPPUpdates SophieBasedEra era
era result'
ProposedPPUpdates ledgerera
r'
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
_ QueryInSophieBasedEra era result
QueryStakeDistribution BlockQuery (SophieBlock ledgerera) result'
q' result'
r' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
BlockQuery (SophieBlock ledgerera) result'
Consensus.GetStakeDistribution -> PoolDistr StandardCrypto -> Map (Hash StakePoolKey) Rational
fromSophiePoolDistr result'
PoolDistr StandardCrypto
r'
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
era (QueryUTxO QueryUTxOFilter
QueryUTxOWhole) BlockQuery (SophieBlock ledgerera) result'
q' result'
utxo' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
BlockQuery (SophieBlock ledgerera) result'
Consensus.GetUTxOWhole -> SophieBasedEra era -> UTxO ledgerera -> UTxO era
forall era ledgerera.
(SophieLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
SophieBasedEra era -> UTxO ledgerera -> UTxO era
fromLedgerUTxO SophieBasedEra era
era result'
UTxO ledgerera
utxo'
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
era (QueryUTxO QueryUTxOByAddress{}) BlockQuery (SophieBlock ledgerera) result'
q' result'
utxo' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
Consensus.GetUTxOByAddress{} -> SophieBasedEra era -> UTxO ledgerera -> UTxO era
forall era ledgerera.
(SophieLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
SophieBasedEra era -> UTxO ledgerera -> UTxO era
fromLedgerUTxO SophieBasedEra era
era result'
UTxO ledgerera
utxo'
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
era (QueryUTxO QueryUTxOByTxIn{}) BlockQuery (SophieBlock ledgerera) result'
q' result'
utxo' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
Consensus.GetUTxOByTxIn{} -> SophieBasedEra era -> UTxO ledgerera -> UTxO era
forall era ledgerera.
(SophieLedgerEra era ~ ledgerera,
Crypto ledgerera ~ StandardCrypto) =>
SophieBasedEra era -> UTxO ledgerera -> UTxO era
fromLedgerUTxO SophieBasedEra era
era result'
UTxO ledgerera
utxo'
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
_ (QueryStakeAddresses Set StakeCredential
_ NetworkId
nId) BlockQuery (SophieBlock ledgerera) result'
q' result'
r' =
case BlockQuery (SophieBlock 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 Entropic -> Map StakeAddress Entropic
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys (NetworkId -> StakeCredential -> StakeAddress
makeStakeAddress NetworkId
nId) (Map StakeCredential Entropic -> Map StakeAddress Entropic)
-> Map StakeCredential Entropic -> Map StakeAddress Entropic
forall a b. (a -> b) -> a -> b
$ RewardAccounts StandardCrypto -> Map StakeCredential Entropic
fromSophieRewardAccounts 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)
fromSophieDelegations Map
(Credential 'Staking StandardCrypto)
(KeyHash 'StakePool StandardCrypto)
delegs
)
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
_ QueryInSophieBasedEra era result
QueryStakePools BlockQuery (SophieBlock ledgerera) result'
q' result'
poolids' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
BlockQuery (SophieBlock 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 (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
_ QueryStakePoolParameters{} BlockQuery (SophieBlock ledgerera) result'
q' result'
poolparams' =
case BlockQuery (SophieBlock 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
fromSophiePoolParams
(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 (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
_ QueryDebugLedgerState{} BlockQuery (SophieBlock ledgerera) result'
q' result'
r' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
Consensus.GetCBOR Consensus.DebugNewEpochState -> Serialised (NewEpochState (SophieLedgerEra era))
-> SerialisedDebugLedgerState era
forall era.
Serialised (NewEpochState (SophieLedgerEra era))
-> SerialisedDebugLedgerState era
SerialisedDebugLedgerState result'
Serialised (NewEpochState (SophieLedgerEra era))
r'
BlockQuery (SophieBlock ledgerera) result'
_ -> result
forall a. a
fromConsensusQueryResultMismatch
fromConsensusQueryResultSophieBased SophieBasedEra era
_ QueryInSophieBasedEra era result
QueryProtocolState BlockQuery (SophieBlock ledgerera) result'
q' result'
r' =
case BlockQuery (SophieBlock ledgerera) result'
q' of
Consensus.GetCBOR Consensus.DebugChainDepState -> Serialised (ChainDepState (Crypto (SophieLedgerEra era)))
-> ProtocolState era
forall era.
Serialised (ChainDepState (Crypto (SophieLedgerEra era)))
-> ProtocolState era
ProtocolState result'
Serialised (ChainDepState (Crypto (SophieLedgerEra era)))
r'
BlockQuery (SophieBlock 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