Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cardano.Api.Internal.Query
Description
Queries from local clients to the node.
Synopsis
- data QueryInMode result where
- QueryCurrentEra :: QueryInMode AnyCardanoEra
- QueryInEra :: forall era result1. QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
- QueryEraHistory :: QueryInMode EraHistory
- QuerySystemStart :: QueryInMode SystemStart
- QueryChainBlockNo :: QueryInMode (WithOrigin BlockNo)
- QueryChainPoint :: QueryInMode ChainPoint
- QueryLedgerConfig :: QueryInMode (HardForkLedgerConfig (CardanoEras StandardCrypto))
- data QueryInEra era result where
- QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState
- QueryInShelleyBasedEra :: forall era result. ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result
- data QueryInShelleyBasedEra era result where
- QueryEpoch :: forall era. QueryInShelleyBasedEra era EpochNo
- QueryGenesisParameters :: forall era. QueryInShelleyBasedEra era (GenesisParameters ShelleyEra)
- QueryProtocolParameters :: forall era. QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era))
- QueryStakeDistribution :: forall era. QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational)
- QueryUTxO :: forall era. QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era)
- QueryStakeAddresses :: forall era. Set StakeCredential -> NetworkId -> QueryInShelleyBasedEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
- QueryStakePools :: forall era. QueryInShelleyBasedEra era (Set PoolId)
- QueryStakePoolParameters :: forall era. Set PoolId -> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
- QueryDebugLedgerState :: forall era. QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
- QueryProtocolState :: forall era. QueryInShelleyBasedEra era (ProtocolState era)
- QueryCurrentEpochState :: forall era. QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
- QueryPoolState :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolState era)
- QueryPoolDistribution :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
- QueryStakeSnapshot :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
- QueryStakeDelegDeposits :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential Coin)
- QueryAccountState :: forall era. QueryInShelleyBasedEra era AccountState
- QueryConstitution :: forall era. QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
- QueryGovState :: forall era. QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era))
- QueryRatifyState :: forall era. QueryInShelleyBasedEra era (RatifyState (ShelleyLedgerEra era))
- QueryFuturePParams :: forall era. QueryInShelleyBasedEra era (Maybe (PParams (ShelleyLedgerEra era)))
- QueryDRepState :: forall era. Set (Credential 'DRepRole) -> QueryInShelleyBasedEra era (Map (Credential 'DRepRole) DRepState)
- QueryDRepStakeDistr :: forall era. Set DRep -> QueryInShelleyBasedEra era (Map DRep Coin)
- QuerySPOStakeDistr :: forall era. Set (KeyHash 'StakePool) -> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin)
- QueryCommitteeMembersState :: forall era. Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> QueryInShelleyBasedEra era CommitteeMembersState
- QueryStakeVoteDelegatees :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential DRep)
- QueryProposals :: forall era. Set GovActionId -> QueryInShelleyBasedEra era (Seq (GovActionState (ShelleyLedgerEra era)))
- QueryLedgerPeerSnapshot :: forall era. QueryInShelleyBasedEra era (Serialised LedgerPeerSnapshot)
- QueryStakePoolDefaultVote :: forall era. KeyHash 'StakePool -> QueryInShelleyBasedEra era DefaultVote
- data QueryUTxOFilter
- data UTxOInAnyEra where
- UTxOInAnyEra :: forall era. CardanoEra era -> UTxO era -> UTxOInAnyEra
- toConsensusQuery :: CardanoBlock StandardCrypto ~ block => QueryInMode result -> Some (Query block)
- fromConsensusQueryResult :: (HasCallStack, CardanoBlock StandardCrypto ~ block) => QueryInMode result -> Query block result' -> result' -> result
- newtype SerialisedDebugLedgerState era = SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era)))
- newtype ProtocolState era = ProtocolState (Serialised (ChainDepState (ConsensusProtocol era)))
- decodeProtocolState :: FromCBOR (ChainDepState (ConsensusProtocol era)) => ProtocolState era -> Either (ByteString, DecoderError) (ChainDepState (ConsensusProtocol era))
- newtype DebugLedgerState era = DebugLedgerState {}
- decodeDebugLedgerState :: FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either (ByteString, DecoderError) (DebugLedgerState era)
- newtype SerialisedCurrentEpochState era = SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era)))
- newtype CurrentEpochState era = CurrentEpochState (EpochState (ShelleyLedgerEra era))
- decodeCurrentEpochState :: ShelleyBasedEra era -> SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState era)
- newtype SerialisedPoolState era = SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era)))
- newtype PoolState era = PoolState (PState (ShelleyLedgerEra era))
- decodePoolState :: (Era (ShelleyLedgerEra era), DecCBOR (PState (ShelleyLedgerEra era))) => SerialisedPoolState era -> Either DecoderError (PoolState era)
- newtype SerialisedPoolDistribution era = SerialisedPoolDistribution (Serialised (PoolDistr StandardCrypto))
- newtype PoolDistribution era = PoolDistribution {}
- decodePoolDistribution :: ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era)
- newtype SerialisedStakeSnapshots era = SerialisedStakeSnapshots (Serialised StakeSnapshots)
- newtype StakeSnapshot era = StakeSnapshot StakeSnapshots
- decodeStakeSnapshot :: SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era)
- data EraHistory where
- EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory
- newtype SystemStart = SystemStart {}
- newtype LedgerEpochInfo = LedgerEpochInfo {}
- toLedgerEpochInfo :: EraHistory -> LedgerEpochInfo
- newtype SlotsInEpoch = SlotsInEpoch Word64
- newtype SlotsToEpochEnd = SlotsToEpochEnd Word64
- slotToEpoch :: SlotNo -> EraHistory -> Either PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
- data family LedgerState blk (mk :: MapKind)
- getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength)
- getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo
- decodeBigLedgerPeerSnapshot :: Serialised LedgerPeerSnapshot -> Either (ByteString, DecoderError) LedgerPeerSnapshot
- toLedgerUTxO :: ShelleyBasedEra era -> UTxO era -> UTxO (ShelleyLedgerEra era)
- fromLedgerUTxO :: ShelleyBasedEra era -> UTxO (ShelleyLedgerEra era) -> UTxO era
Queries
data QueryInMode result where Source #
Constructors
QueryCurrentEra :: QueryInMode AnyCardanoEra | |
QueryInEra :: forall era result1. QueryInEra era result1 -> QueryInMode (Either EraMismatch result1) | |
QueryEraHistory :: QueryInMode EraHistory | |
QuerySystemStart :: QueryInMode SystemStart | |
QueryChainBlockNo :: QueryInMode (WithOrigin BlockNo) | |
QueryChainPoint :: QueryInMode ChainPoint | |
QueryLedgerConfig :: QueryInMode (HardForkLedgerConfig (CardanoEras StandardCrypto)) |
Instances
Show (QueryInMode result) Source # | |
Defined in Cardano.Api.Internal.Query |
data QueryInEra era result where Source #
Constructors
QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState | |
QueryInShelleyBasedEra :: forall era result. ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result |
Instances
Show (QueryInEra era result) Source # | |
Defined in Cardano.Api.Internal.Query |
data QueryInShelleyBasedEra era result where Source #
Constructors
Instances
Show (QueryInShelleyBasedEra era result) Source # | |
Defined in Cardano.Api.Internal.Query |
data QueryUTxOFilter Source #
Getting the whole UTxO is obviously not efficient since the result can be huge. Filtering by address is also not efficient because it requires a linear search.
The QueryUTxOFilterByTxIn
is efficient since it fits with the structure of
the UTxO (which is indexed by TxIn
).
Constructors
QueryUTxOWhole | O(n) time and space for utxo size n |
QueryUTxOByAddress (Set AddressAny) | O(n) time, O(m) space for utxo size n, and address set size m |
QueryUTxOByTxIn (Set TxIn) | O(m log n) time, O(m) space for utxo size n, and address set size m |
Instances
Show QueryUTxOFilter Source # | |
Defined in Cardano.Api.Internal.Query | |
Eq QueryUTxOFilter Source # | |
Defined in Cardano.Api.Internal.Query Methods (==) :: QueryUTxOFilter -> QueryUTxOFilter -> Bool Source # (/=) :: QueryUTxOFilter -> QueryUTxOFilter -> Bool Source # |
data UTxOInAnyEra where Source #
Constructors
UTxOInAnyEra :: forall era. CardanoEra era -> UTxO era -> UTxOInAnyEra |
Instances
Show UTxOInAnyEra Source # | |
Defined in Cardano.Api.Internal.Query |
Internal conversion functions
toConsensusQuery :: CardanoBlock StandardCrypto ~ block => QueryInMode result -> Some (Query block) Source #
fromConsensusQueryResult :: (HasCallStack, CardanoBlock StandardCrypto ~ block) => QueryInMode result -> Query block result' -> result' -> result Source #
Wrapper types used in queries
newtype SerialisedDebugLedgerState era Source #
Constructors
SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era))) |
newtype ProtocolState era Source #
Constructors
ProtocolState (Serialised (ChainDepState (ConsensusProtocol era))) |
decodeProtocolState :: FromCBOR (ChainDepState (ConsensusProtocol era)) => ProtocolState era -> Either (ByteString, DecoderError) (ChainDepState (ConsensusProtocol era)) Source #
newtype DebugLedgerState era Source #
Constructors
DebugLedgerState | |
Fields |
Instances
IsShelleyBasedEra era => ToJSON (DebugLedgerState era) Source # | |
Defined in Cardano.Api.Internal.Query.Types Methods toJSON :: DebugLedgerState era -> Value toEncoding :: DebugLedgerState era -> Encoding toJSONList :: [DebugLedgerState era] -> Value toEncodingList :: [DebugLedgerState era] -> Encoding omitField :: DebugLedgerState era -> Bool | |
IsShelleyBasedEra era => FromCBOR (DebugLedgerState era) Source # | |
Defined in Cardano.Api.Internal.Query.Types |
decodeDebugLedgerState :: FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either (ByteString, DecoderError) (DebugLedgerState era) Source #
newtype SerialisedCurrentEpochState era Source #
Constructors
SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era))) |
newtype CurrentEpochState era Source #
Constructors
CurrentEpochState (EpochState (ShelleyLedgerEra era)) |
decodeCurrentEpochState :: ShelleyBasedEra era -> SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState era) Source #
newtype SerialisedPoolState era Source #
Constructors
SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era))) |
decodePoolState :: (Era (ShelleyLedgerEra era), DecCBOR (PState (ShelleyLedgerEra era))) => SerialisedPoolState era -> Either DecoderError (PoolState era) Source #
newtype SerialisedPoolDistribution era Source #
Constructors
SerialisedPoolDistribution (Serialised (PoolDistr StandardCrypto)) |
newtype PoolDistribution era Source #
Constructors
PoolDistribution | |
Fields |
decodePoolDistribution :: ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era) Source #
newtype SerialisedStakeSnapshots era Source #
Constructors
SerialisedStakeSnapshots (Serialised StakeSnapshots) |
newtype StakeSnapshot era Source #
Constructors
StakeSnapshot StakeSnapshots |
decodeStakeSnapshot :: SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era) Source #
data EraHistory where Source #
Constructors
EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory |
Instances
HasTypeProxy EraHistory Source # | |||||
Defined in Cardano.Api.Internal.Query Associated Types
Methods proxyToAsType :: Proxy EraHistory -> AsType EraHistory Source # | |||||
SerialiseAsCBOR EraHistory Source # | |||||
Defined in Cardano.Api.Internal.Query Methods serialiseToCBOR :: EraHistory -> ByteString Source # deserialiseFromCBOR :: AsType EraHistory -> ByteString -> Either DecoderError EraHistory Source # | |||||
HasTextEnvelope EraHistory Source # | The | ||||
Defined in Cardano.Api.Internal.Query | |||||
data AsType EraHistory Source # | |||||
Defined in Cardano.Api.Internal.Query |
newtype SystemStart Source #
System start
Slots are counted from the system start.
Constructors
SystemStart | |
Fields |
Instances
newtype LedgerEpochInfo Source #
Constructors
LedgerEpochInfo | |
Fields |
newtype SlotsInEpoch Source #
Constructors
SlotsInEpoch Word64 |
newtype SlotsToEpochEnd Source #
Constructors
SlotsToEpochEnd Word64 |
slotToEpoch :: SlotNo -> EraHistory -> Either PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd) Source #
data family LedgerState blk (mk :: MapKind) Source #
Ledger state associated with a block
This is the Consensus notion of a Ledger ledger state. Each block type is
associated with one of the Ledger types for the ledger state. Virtually
every concept in this codebase revolves around this type, or the referenced
blk
. Whenever we use the type variable l
we intend to signal that the
expected instantiation is either a LedgerState
or some wrapper over it
(like the ExtLedgerState
).
This type is parametrized over mk ::
to express the
MapKind
LedgerTables
contained in such a LedgerState
. See LedgerTables
for a
more thorough description.
The main operations we can do with a LedgerState
are ticking (defined in
IsLedger
), and applying a block (defined in
ApplyBlock
).
Instances
Bridge m a => GetTip (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods getTip :: forall (mk :: MapKind). LedgerState (DualBlock m a) mk -> Point (LedgerState (DualBlock m a)) Source # | |||||||||
Bridge m a => IsLedger (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Associated Types
Methods applyChainTickLedgerResult :: ComputeLedgerEvents -> LedgerCfg (LedgerState (DualBlock m a)) -> SlotNo -> LedgerState (DualBlock m a) EmptyMK -> LedgerResult (LedgerState (DualBlock m a)) (Ticked (LedgerState (DualBlock m a)) DiffMK) Source # | |||||||||
CanStowLedgerTables (LedgerState m) => CanStowLedgerTables (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods stowLedgerTables :: LedgerState (DualBlock m a) ValuesMK -> LedgerState (DualBlock m a) EmptyMK Source # unstowLedgerTables :: LedgerState (DualBlock m a) EmptyMK -> LedgerState (DualBlock m a) ValuesMK Source # | |||||||||
(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) => HasLedgerTables (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods projectLedgerTables :: forall (mk :: MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) => LedgerState (DualBlock m a) mk -> LedgerTables (LedgerState (DualBlock m a)) mk Source # withLedgerTables :: forall (mk :: MapKind) (any :: MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) => LedgerState (DualBlock m a) any -> LedgerTables (LedgerState (DualBlock m a)) mk -> LedgerState (DualBlock m a) mk Source # | |||||||||
(Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m)), MemPack (TxOut (LedgerState m))) => SerializeTablesWithHint (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods encodeTablesWithHint :: SerializeTablesHint (LedgerTables (LedgerState (DualBlock m a)) ValuesMK) -> LedgerTables (LedgerState (DualBlock m a)) ValuesMK -> Encoding Source # decodeTablesWithHint :: SerializeTablesHint (LedgerTables (LedgerState (DualBlock m a)) ValuesMK) -> Decoder s (LedgerTables (LedgerState (DualBlock m a)) ValuesMK) Source # | |||||||||
CanUpgradeLedgerTables (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods upgradeTables :: forall (mk1 :: MapKind) (mk2 :: MapKind). LedgerState (DualBlock m a) mk1 -> LedgerState (DualBlock m a) mk2 -> LedgerTables (LedgerState (DualBlock m a)) ValuesMK -> LedgerTables (LedgerState (DualBlock m a)) ValuesMK Source # | |||||||||
Bridge m a => ApplyBlock (LedgerState (DualBlock m a)) (DualBlock m a) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods applyBlockLedgerResultWithValidation :: ValidationPolicy -> ComputeLedgerEvents -> LedgerCfg (LedgerState (DualBlock m a)) -> DualBlock m a -> Ticked (LedgerState (DualBlock m a)) ValuesMK -> Except (LedgerErr (LedgerState (DualBlock m a))) (LedgerResult (LedgerState (DualBlock m a)) (LedgerState (DualBlock m a) DiffMK)) Source # applyBlockLedgerResult :: ComputeLedgerEvents -> LedgerCfg (LedgerState (DualBlock m a)) -> DualBlock m a -> Ticked (LedgerState (DualBlock m a)) ValuesMK -> Except (LedgerErr (LedgerState (DualBlock m a))) (LedgerResult (LedgerState (DualBlock m a)) (LedgerState (DualBlock m a) DiffMK)) Source # reapplyBlockLedgerResult :: ComputeLedgerEvents -> LedgerCfg (LedgerState (DualBlock m a)) -> DualBlock m a -> Ticked (LedgerState (DualBlock m a)) ValuesMK -> LedgerResult (LedgerState (DualBlock m a)) (LedgerState (DualBlock m a) DiffMK) Source # getBlockKeySets :: DualBlock m a -> LedgerTables (LedgerState (DualBlock m a)) KeysMK Source # | |||||||||
(ShowMK mk, CanHardFork xs) => Show (LedgerState (HardForkBlock xs) mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods showsPrec :: Int -> LedgerState (HardForkBlock xs) mk -> ShowS Source # show :: LedgerState (HardForkBlock xs) mk -> String Source # showList :: [LedgerState (HardForkBlock xs) mk] -> ShowS Source # | |||||||||
(Bridge m a, ShowMK mk) => Show (LedgerState (DualBlock m a) mk) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
(EqMK mk, CanHardFork xs) => Eq (LedgerState (HardForkBlock xs) mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods (==) :: LedgerState (HardForkBlock xs) mk -> LedgerState (HardForkBlock xs) mk -> Bool Source # (/=) :: LedgerState (HardForkBlock xs) mk -> LedgerState (HardForkBlock xs) mk -> Bool Source # | |||||||||
(Bridge m a, EqMK mk) => Eq (LedgerState (DualBlock m a) mk) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods (==) :: LedgerState (DualBlock m a) mk -> LedgerState (DualBlock m a) mk -> Bool Source # (/=) :: LedgerState (DualBlock m a) mk -> LedgerState (DualBlock m a) mk -> Bool Source # | |||||||||
(NoThunksMK mk, CanHardFork xs) => NoThunks (LedgerState (HardForkBlock xs) mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks :: Context -> LedgerState (HardForkBlock xs) mk -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> LedgerState (HardForkBlock xs) mk -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (LedgerState (HardForkBlock xs) mk) -> String # | |||||||||
NoThunks (LedgerState (DualBlock m a) mk) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods noThunks :: Context -> LedgerState (DualBlock m a) mk -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> LedgerState (DualBlock m a) mk -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (LedgerState (DualBlock m a) mk) -> String # | |||||||||
Bridge m a => GetTip (Ticked (LedgerState (DualBlock m a))) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) => HasLedgerTables (Ticked (LedgerState (DualBlock m a))) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods projectLedgerTables :: forall (mk :: MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) => Ticked (LedgerState (DualBlock m a)) mk -> LedgerTables (Ticked (LedgerState (DualBlock m a))) mk Source # withLedgerTables :: forall (mk :: MapKind) (any :: MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) => Ticked (LedgerState (DualBlock m a)) any -> LedgerTables (Ticked (LedgerState (DualBlock m a))) mk -> Ticked (LedgerState (DualBlock m a)) mk Source # | |||||||||
(txout ~ TxOut (LedgerState m), IndexedMemPack (LedgerState m EmptyMK) txout) => IndexedMemPack (LedgerState (DualBlock m a) EmptyMK) txout | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods indexedPackedByteCount :: LedgerState (DualBlock m a) EmptyMK -> txout -> Int Source # indexedPackM :: LedgerState (DualBlock m a) EmptyMK -> txout -> Pack s () Source # indexedUnpackM :: Buffer b => LedgerState (DualBlock m a) EmptyMK -> Unpack b txout Source # indexedTypeName :: LedgerState (DualBlock m a) EmptyMK -> String Source # | |||||||||
CardanoHardForkConstraints c => IndexedMemPack (LedgerState (HardForkBlock (CardanoEras c)) EmptyMK) (CardanoTxOut c) | |||||||||
Defined in Ouroboros.Consensus.Cardano.Ledger Methods indexedPackedByteCount :: LedgerState (HardForkBlock (CardanoEras c)) EmptyMK -> CardanoTxOut c -> Int Source # indexedPackM :: LedgerState (HardForkBlock (CardanoEras c)) EmptyMK -> CardanoTxOut c -> Pack s () Source # indexedUnpackM :: Buffer b => LedgerState (HardForkBlock (CardanoEras c)) EmptyMK -> Unpack b (CardanoTxOut c) Source # indexedTypeName :: LedgerState (HardForkBlock (CardanoEras c)) EmptyMK -> String Source # | |||||||||
StandardHash blk => StandardHash (LedgerState blk :: MapKind -> Type) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Basics | |||||||||
NoThunks (Ticked (LedgerState (DualBlock m a)) mk) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
Inject (Flip LedgerState mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary Methods inject :: forall x (xs :: [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) => InjectionIndex xs x -> Flip LedgerState mk x -> Flip LedgerState mk (HardForkBlock xs) Source # | |||||||||
Isomorphic (Flip LedgerState mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project :: NoHardForks blk => Flip LedgerState mk (HardForkBlock '[blk]) -> Flip LedgerState mk blk Source # inject :: NoHardForks blk => Flip LedgerState mk blk -> Flip LedgerState mk (HardForkBlock '[blk]) Source # | |||||||||
data LedgerState ByronBlock mk | |||||||||
type TranslationError era (Flip LedgerState mk :.: ShelleyBlock proto) | |||||||||
Defined in Ouroboros.Consensus.Shelley.ShelleyHFC | |||||||||
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) | |||||||||
type AuxLedgerEvent (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type AuxLedgerEvent (LedgerState ByronBlock) | |||||||||
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger | |||||||||
type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) | |||||||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger | |||||||||
type LedgerCfg (LedgerState (HardForkBlock xs)) | |||||||||
type LedgerCfg (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type LedgerCfg (LedgerState ByronBlock) | |||||||||
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger | |||||||||
type LedgerCfg (LedgerState (ShelleyBlock proto era)) | |||||||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger | |||||||||
type LedgerErr (LedgerState (HardForkBlock xs)) | |||||||||
type LedgerErr (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type LedgerErr (LedgerState ByronBlock) | |||||||||
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger | |||||||||
type LedgerErr (LedgerState (ShelleyBlock proto era)) | |||||||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger | |||||||||
newtype LedgerState (HardForkBlock xs) mk | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics newtype LedgerState (HardForkBlock xs) mk = HardForkLedgerState {
| |||||||||
type TxIn (LedgerState (HardForkBlock xs)) | Must be the | ||||||||
type TxIn (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type TxIn (LedgerState ByronBlock) | |||||||||
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger | |||||||||
type TxIn (LedgerState (ShelleyBlock proto era)) | |||||||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger | |||||||||
type TxOut (LedgerState (HardForkBlock xs)) | Must be the | ||||||||
type TxOut (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type TxOut (LedgerState ByronBlock) | |||||||||
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger | |||||||||
type TxOut (LedgerState (ShelleyBlock proto era)) | |||||||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger | |||||||||
type Rep (LedgerState ByronBlock mk) | |||||||||
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger type Rep (LedgerState ByronBlock mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.0.0-2ce8ee823d5ca2d71f0812e7c0aa9774e3c75e5e441e59adaf57b624111984f6" 'False) (C1 ('MetaCons "ByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "byronLedgerTipBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin BlockNo)) :*: (S1 ('MetaSel ('Just "byronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "byronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ByronTransition)))) | |||||||||
type Rep (LedgerState (ShelleyBlock proto era) mk) | |||||||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger type Rep (LedgerState (ShelleyBlock proto era) mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.0.0-2ce8ee823d5ca2d71f0812e7c0aa9774e3c75e5e441e59adaf57b624111984f6" 'False) (C1 ('MetaCons "ShelleyLedgerState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "shelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: S1 ('MetaSel ('Just "shelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era))) :*: (S1 ('MetaSel ('Just "shelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShelleyTransition) :*: S1 ('MetaSel ('Just "shelleyLedgerTables") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerTables (LedgerState (ShelleyBlock proto era)) mk))))) | |||||||||
data LedgerState (DualBlock m a) mk | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
data LedgerState (ShelleyBlock proto era) mk | |||||||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger data LedgerState (ShelleyBlock proto era) mk = ShelleyLedgerState {
| |||||||||
data Ticked (LedgerState (HardForkBlock xs) :: MapKind -> Type) (mk :: MapKind) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger data Ticked (LedgerState (HardForkBlock xs) :: MapKind -> Type) (mk :: MapKind) = TickedHardForkLedgerState {} | |||||||||
data Ticked (LedgerState (DualBlock m a) :: MapKind -> Type) (mk :: MapKind) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual data Ticked (LedgerState (DualBlock m a) :: MapKind -> Type) (mk :: MapKind) = TickedDualLedgerState {} | |||||||||
data Ticked (LedgerState ByronBlock) (mk :: MapKind) | The ticked Byron ledger state | ||||||||
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger | |||||||||
data Ticked (LedgerState (ShelleyBlock proto era) :: MapKind -> Type) (mk :: MapKind) | Ticking only affects the state itself | ||||||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger data Ticked (LedgerState (ShelleyBlock proto era) :: MapKind -> Type) (mk :: MapKind) = TickedShelleyLedgerState {
| |||||||||
type HeaderHash (LedgerState blk :: MapKind -> Type) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Basics | |||||||||
type Rep (Ticked (LedgerState ByronBlock) mk) | |||||||||
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger type Rep (Ticked (LedgerState ByronBlock) mk) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.0.0-2ce8ee823d5ca2d71f0812e7c0aa9774e3c75e5e441e59adaf57b624111984f6" 'False) (C1 ('MetaCons "TickedByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedByronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "untickedByronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ByronTransition))) | |||||||||
type Rep (Ticked (LedgerState (ShelleyBlock proto era)) mk) | |||||||||
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger type Rep (Ticked (LedgerState (ShelleyBlock proto era)) mk) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.0.0-2ce8ee823d5ca2d71f0812e7c0aa9774e3c75e5e441e59adaf57b624111984f6" 'False) (C1 ('MetaCons "TickedShelleyLedgerState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "untickedShelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ShelleyTransition)) :*: (S1 ('MetaSel ('Just "tickedShelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerTables") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerTables (LedgerState (ShelleyBlock proto era)) mk))))) |
getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength) Source #
getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo Source #
Returns the slot number for provided relative time from SystemStart
decodeBigLedgerPeerSnapshot :: Serialised LedgerPeerSnapshot -> Either (ByteString, DecoderError) LedgerPeerSnapshot Source #
Internal conversion functions
toLedgerUTxO :: ShelleyBasedEra era -> UTxO era -> UTxO (ShelleyLedgerEra era) Source #
fromLedgerUTxO :: ShelleyBasedEra era -> UTxO (ShelleyLedgerEra era) -> UTxO era Source #