Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cardano.Api.Query
Description
Queries from local clients to the node.
Synopsis
- data QueryInMode result where
- QueryCurrentEra :: QueryInMode AnyCardanoEra
- QueryInEra :: QueryInEra era result -> QueryInMode (Either EraMismatch result)
- QueryEraHistory :: QueryInMode EraHistory
- QuerySystemStart :: QueryInMode SystemStart
- QueryChainBlockNo :: QueryInMode (WithOrigin BlockNo)
- QueryChainPoint :: QueryInMode ChainPoint
- data QueryInEra era result where
- QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState
- QueryInShelleyBasedEra :: ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result
- data QueryInShelleyBasedEra era result where
- QueryEpoch :: QueryInShelleyBasedEra era EpochNo
- QueryGenesisParameters :: QueryInShelleyBasedEra era (GenesisParameters ShelleyEra)
- QueryProtocolParameters :: QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era))
- QueryProtocolParametersUpdate :: QueryInShelleyBasedEra era (Map (Hash GenesisKey) ProtocolParametersUpdate)
- QueryStakeDistribution :: QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational)
- QueryUTxO :: QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era)
- QueryStakeAddresses :: Set StakeCredential -> NetworkId -> QueryInShelleyBasedEra era (Map StakeAddress Lovelace, Map StakeAddress PoolId)
- QueryStakePools :: QueryInShelleyBasedEra era (Set PoolId)
- QueryStakePoolParameters :: Set PoolId -> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
- QueryDebugLedgerState :: QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
- QueryProtocolState :: QueryInShelleyBasedEra era (ProtocolState era)
- QueryCurrentEpochState :: QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
- QueryPoolState :: Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolState era)
- QueryPoolDistribution :: Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
- QueryStakeSnapshot :: Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
- QueryStakeDelegDeposits :: Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential Lovelace)
- QueryConstitution :: QueryInShelleyBasedEra era (Maybe (Constitution (ShelleyLedgerEra era)))
- QueryGovState :: QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era))
- QueryDRepState :: Set (Credential DRepRole StandardCrypto) -> QueryInShelleyBasedEra era (Map (Credential DRepRole StandardCrypto) (DRepState StandardCrypto))
- QueryDRepStakeDistr :: Set (DRep StandardCrypto) -> QueryInShelleyBasedEra era (Map (DRep StandardCrypto) Lovelace)
- QueryCommitteeMembersState :: Set (Credential ColdCommitteeRole StandardCrypto) -> Set (Credential HotCommitteeRole StandardCrypto) -> Set MemberStatus -> QueryInShelleyBasedEra era (Maybe (CommitteeMembersState StandardCrypto))
- QueryStakeVoteDelegatees :: Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential (DRep StandardCrypto))
- data QueryUTxOFilter
- = QueryUTxOWhole
- | QueryUTxOByAddress (Set AddressAny)
- | QueryUTxOByTxIn (Set TxIn)
- newtype UTxO era = UTxO {}
- data UTxOInAnyEra where
- UTxOInAnyEra :: CardanoEra era -> UTxO era -> UTxOInAnyEra
- toConsensusQuery :: forall block result. CardanoBlock StandardCrypto ~ block => QueryInMode result -> Some (Query block)
- fromConsensusQueryResult :: forall block result result'. 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 {
- unDebugLedgerState :: NewEpochState (ShelleyLedgerEra era)
- decodeDebugLedgerState :: forall era. FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either ByteString (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 :: forall era. Era (ShelleyLedgerEra era) => DecCBOR (PState (ShelleyLedgerEra era)) => SerialisedPoolState era -> Either DecoderError (PoolState era)
- newtype SerialisedPoolDistribution era = SerialisedPoolDistribution (Serialised (PoolDistr (EraCrypto (ShelleyLedgerEra era))))
- newtype PoolDistribution era = PoolDistribution {
- unPoolDistr :: PoolDistr (EraCrypto (ShelleyLedgerEra era))
- decodePoolDistribution :: forall era. Crypto (EraCrypto (ShelleyLedgerEra era)) => ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era)
- newtype SerialisedStakeSnapshots era = SerialisedStakeSnapshots (Serialised (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))))
- newtype StakeSnapshot era = StakeSnapshot (StakeSnapshots (EraCrypto (ShelleyLedgerEra era)))
- decodeStakeSnapshot :: forall era. FromCBOR (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) => SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era)
- data EraHistory where
- EraHistory :: CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory
- newtype SystemStart = SystemStart {
- getSystemStart :: UTCTime
- newtype LedgerEpochInfo = LedgerEpochInfo {
- unLedgerEpochInfo :: EpochInfo (Either Text)
- toLedgerEpochInfo :: EraHistory -> LedgerEpochInfo
- newtype SlotsInEpoch = SlotsInEpoch Word64
- newtype SlotsToEpochEnd = SlotsToEpochEnd Word64
- slotToEpoch :: SlotNo -> EraHistory -> Either PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
- data family LedgerState blk
- getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength)
- getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo
- 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 :: QueryInEra era result -> QueryInMode (Either EraMismatch result) | |
QueryEraHistory :: QueryInMode EraHistory | |
QuerySystemStart :: QueryInMode SystemStart | |
QueryChainBlockNo :: QueryInMode (WithOrigin BlockNo) | |
QueryChainPoint :: QueryInMode ChainPoint |
Instances
Show (QueryInMode result) Source # | |
Defined in Cardano.Api.Query | |
NodeToClientVersionOf (QueryInMode result) Source # | |
Defined in Cardano.Api.Query Methods nodeToClientVersionOf :: QueryInMode result -> NodeToClientVersion Source # |
data QueryInEra era result where Source #
Constructors
QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState | |
QueryInShelleyBasedEra :: ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result |
Instances
Show (QueryInEra era result) Source # | |
Defined in Cardano.Api.Query | |
NodeToClientVersionOf (QueryInEra era result) Source # | |
Defined in Cardano.Api.Query Methods nodeToClientVersionOf :: QueryInEra era result -> NodeToClientVersion Source # |
data QueryInShelleyBasedEra era result where Source #
Constructors
Instances
Show (QueryInShelleyBasedEra era result) Source # | |
Defined in Cardano.Api.Query | |
NodeToClientVersionOf (QueryInShelleyBasedEra era result) Source # | Mapping for queries in Shelley-based eras returning minimal node-to-client protocol versions. More information about queries versioning can be found: * https://input-output-hk.github.io/ouroboros-network/ouroboros-network/Ouroboros-Network-NodeToClient.html#t:NodeToClientVersion * https://input-output-hk.github.io/ouroboros-consensus/docs/for-developers/QueryVersioning/#implementation |
Defined in Cardano.Api.Query Methods nodeToClientVersionOf :: QueryInShelleyBasedEra era result -> NodeToClientVersion Source # |
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
Eq QueryUTxOFilter Source # | |
Defined in Cardano.Api.Query Methods (==) :: QueryUTxOFilter -> QueryUTxOFilter -> Bool Source # (/=) :: QueryUTxOFilter -> QueryUTxOFilter -> Bool Source # | |
Show QueryUTxOFilter Source # | |
Defined in Cardano.Api.Query | |
NodeToClientVersionOf QueryUTxOFilter Source # | |
Defined in Cardano.Api.Query Methods nodeToClientVersionOf :: QueryUTxOFilter -> NodeToClientVersion Source # |
Instances
Eq (UTxO era) Source # | |
Show (UTxO era) Source # | |
(IsShelleyBasedEra era, FromJSON (TxOut CtxUTxO era)) => FromJSON (UTxO era) Source # | |
Defined in Cardano.Api.Query Methods parseJSON :: Value -> Parser (UTxO era) # parseJSONList :: Value -> Parser [UTxO era] # omittedField :: Maybe (UTxO era) # | |
IsCardanoEra era => ToJSON (UTxO era) Source # | |
Defined in Cardano.Api.Query |
data UTxOInAnyEra where Source #
Constructors
UTxOInAnyEra :: CardanoEra era -> UTxO era -> UTxOInAnyEra |
Instances
Show UTxOInAnyEra Source # | |
Defined in Cardano.Api.Query |
Internal conversion functions
toConsensusQuery :: forall block result. CardanoBlock StandardCrypto ~ block => QueryInMode result -> Some (Query block) Source #
fromConsensusQueryResult :: forall block result result'. 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 => FromCBOR (DebugLedgerState era) Source # | |
Defined in Cardano.Api.Query.Types Methods fromCBOR :: Decoder s (DebugLedgerState era) # label :: Proxy (DebugLedgerState era) -> Text # | |
IsShelleyBasedEra era => ToJSON (DebugLedgerState era) Source # | |
Defined in Cardano.Api.Query.Types Methods toJSON :: DebugLedgerState era -> Value # toEncoding :: DebugLedgerState era -> Encoding # toJSONList :: [DebugLedgerState era] -> Value # toEncodingList :: [DebugLedgerState era] -> Encoding # omitField :: DebugLedgerState era -> Bool # |
decodeDebugLedgerState :: forall era. FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either ByteString (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))) |
newtype PoolState era Source #
Constructors
PoolState (PState (ShelleyLedgerEra era)) |
decodePoolState :: forall era. Era (ShelleyLedgerEra era) => DecCBOR (PState (ShelleyLedgerEra era)) => SerialisedPoolState era -> Either DecoderError (PoolState era) Source #
newtype SerialisedPoolDistribution era Source #
Constructors
SerialisedPoolDistribution (Serialised (PoolDistr (EraCrypto (ShelleyLedgerEra era)))) |
newtype PoolDistribution era Source #
Constructors
PoolDistribution | |
Fields
|
decodePoolDistribution :: forall era. Crypto (EraCrypto (ShelleyLedgerEra era)) => ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era) Source #
newtype SerialisedStakeSnapshots era Source #
Constructors
SerialisedStakeSnapshots (Serialised (StakeSnapshots (EraCrypto (ShelleyLedgerEra era)))) |
newtype StakeSnapshot era Source #
Constructors
StakeSnapshot (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) |
decodeStakeSnapshot :: forall era. FromCBOR (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) => SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era) Source #
data EraHistory where Source #
Constructors
EraHistory :: CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory |
newtype SystemStart #
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 #
Instances
Isomorphic LedgerState | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project :: NoHardForks blk => LedgerState (HardForkBlock '[blk]) -> LedgerState blk inject :: NoHardForks blk => LedgerState blk -> LedgerState (HardForkBlock '[blk]) | |
CanHardFork xs => Eq (LedgerState (HardForkBlock xs)) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods (==) :: LedgerState (HardForkBlock xs) -> LedgerState (HardForkBlock xs) -> Bool Source # (/=) :: LedgerState (HardForkBlock xs) -> LedgerState (HardForkBlock xs) -> Bool Source # | |
CanHardFork xs => Show (LedgerState (HardForkBlock xs)) | |
CanHardFork xs => NoThunks (LedgerState (HardForkBlock xs)) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks :: Context -> LedgerState (HardForkBlock xs) -> IO (Maybe ThunkInfo) wNoThunks :: Context -> LedgerState (HardForkBlock xs) -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (LedgerState (HardForkBlock xs)) -> String | |
Isomorphic (Ticked :.: LedgerState) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project :: NoHardForks blk => (Ticked :.: LedgerState) (HardForkBlock '[blk]) -> (Ticked :.: LedgerState) blk inject :: NoHardForks blk => (Ticked :.: LedgerState) blk -> (Ticked :.: LedgerState) (HardForkBlock '[blk]) | |
data LedgerState ByronBlock | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger data LedgerState ByronBlock = ByronLedgerState {
| |
type HeaderHash (LedgerState blk :: Type) | |
Defined in Ouroboros.Consensus.Ledger.Basics | |
type TranslationError era (LedgerState :.: ShelleyBlock proto) | |
Defined in Ouroboros.Consensus.Shelley.ShelleyHFC | |
type Rep (LedgerState ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger type Rep (LedgerState ByronBlock) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-Eqi8jwiFHKoKVljS76Ugkh" '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)) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger type Rep (LedgerState (ShelleyBlock proto era)) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-Eqi8jwiFHKoKVljS76Ugkh" '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)))) | |
type Rep (Ticked (LedgerState ByronBlock)) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger type Rep (Ticked (LedgerState ByronBlock)) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-Eqi8jwiFHKoKVljS76Ugkh" '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 (HardForkBlock xs))) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.14.0.0-Pi7Pac7NlEeztBZ96b84" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs)))) | |
type Rep (Ticked (LedgerState (ShelleyBlock proto era))) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger type Rep (Ticked (LedgerState (ShelleyBlock proto era))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-Eqi8jwiFHKoKVljS76Ugkh" '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))))) | |
type AuxLedgerEvent (LedgerState ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger | |
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger type AuxLedgerEvent (LedgerState (HardForkBlock xs)) = OneEraLedgerEvent xs | |
type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerEvent era | |
type LedgerErr (LedgerState ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger type LedgerErr (LedgerState ByronBlock) = ChainValidationError | |
type LedgerErr (LedgerState (HardForkBlock xs)) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger type LedgerErr (LedgerState (HardForkBlock xs)) = HardForkLedgerError xs | |
type LedgerErr (LedgerState (ShelleyBlock proto era)) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger type LedgerErr (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerError era | |
type LedgerCfg (LedgerState ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger type LedgerCfg (LedgerState ByronBlock) = Config | |
type LedgerCfg (LedgerState (HardForkBlock xs)) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics type LedgerCfg (LedgerState (HardForkBlock xs)) = HardForkLedgerConfig xs | |
type LedgerCfg (LedgerState (ShelleyBlock proto era)) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger type LedgerCfg (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerConfig era | |
newtype LedgerState (HardForkBlock xs) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics newtype LedgerState (HardForkBlock xs) = HardForkLedgerState {
| |
data Ticked (LedgerState ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger data Ticked (LedgerState ByronBlock) = TickedByronLedgerState {
| |
data Ticked (LedgerState (HardForkBlock xs)) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger data Ticked (LedgerState (HardForkBlock xs)) = TickedHardForkLedgerState {
| |
data Ticked (LedgerState (ShelleyBlock proto era)) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger data Ticked (LedgerState (ShelleyBlock proto era)) = TickedShelleyLedgerState {
| |
data LedgerState (ShelleyBlock proto era) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger data LedgerState (ShelleyBlock proto era) = ShelleyLedgerState {
|
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
Internal conversion functions
toLedgerUTxO :: ShelleyBasedEra era -> UTxO era -> UTxO (ShelleyLedgerEra era) Source #
fromLedgerUTxO :: ShelleyBasedEra era -> UTxO (ShelleyLedgerEra era) -> UTxO era Source #