ouroboros-consensus-cardano-0.24.0.0: The instantation of the Ouroboros consensus layer used by Cardano
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.Shelley.Ledger.Query

Synopsis

Documentation

data family BlockQueryTypeQueryFootprintTypeType Source #

Different queries supported by the ledger, indexed by the result type.

Instances

Instances details
SerialiseBlockQueryResult ByronBlock BlockQuery Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

SameDepIndex2 (BlockQuery (DualBlock m a) ∷ QueryFootprintTypeType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a0 (y ∷ QueryFootprint) b. BlockQuery (DualBlock m a) x a0 → BlockQuery (DualBlock m a) y b → Maybe ('(x, a0) :~: '(y, b)) Source #

SameDepIndex2 (BlockQuery ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery ByronBlock x a → BlockQuery ByronBlock y b → Maybe ('(x, a) :~: '(y, b)) Source #

SameDepIndex2 (BlockQuery (ShelleyBlock proto era) ∷ QueryFootprintTypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery (ShelleyBlock proto era) x a → BlockQuery (ShelleyBlock proto era) y b → Maybe ('(x, a) :~: '(y, b)) Source #

SerialiseNodeToClient ByronBlock (SomeBlockQuery (BlockQuery ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

ShelleyCompatible proto era ⇒ SerialiseBlockQueryResult (ShelleyBlock proto era) BlockQuery Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) fp result → result → Encoding Source #

decodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) fp result → ∀ s. Decoder s result Source #

(∀ (footprint ∷ QueryFootprint) result. Show (BlockQuery blk footprint result)) ⇒ Show (SomeBlockQuery (BlockQuery blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

ShowQuery (BlockQuery (DualBlock m a) footprint) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showResultBlockQuery (DualBlock m a) footprint result → result → String Source #

ShowQuery (BlockQuery ByronBlock fp) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

showResultBlockQuery ByronBlock fp result → result → String Source #

ShelleyCompatible proto era ⇒ ShowQuery (BlockQuery (ShelleyBlock proto era) fp) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showResultBlockQuery (ShelleyBlock proto era) fp result → result → String Source #

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (SomeBlockQuery (BlockQuery (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

(Typeable m, Typeable a) ⇒ ShowProxy (BlockQuery (DualBlock m a) ∷ QueryFootprintTypeType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ShowProxy (BlockQuery ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

(Typeable era, Typeable proto) ⇒ ShowProxy (BlockQuery (ShelleyBlock proto era) ∷ QueryFootprintTypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showProxyProxy (BlockQuery (ShelleyBlock proto era)) → String Source #

Show (BlockQuery (DualBlock m a) footprint result) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntBlockQuery (DualBlock m a) footprint result → ShowS #

showBlockQuery (DualBlock m a) footprint result → String #

showList ∷ [BlockQuery (DualBlock m a) footprint result] → ShowS #

Show (BlockQuery ByronBlock fp result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

showsPrecIntBlockQuery ByronBlock fp result → ShowS #

showBlockQuery ByronBlock fp result → String #

showList ∷ [BlockQuery ByronBlock fp result] → ShowS #

Show (BlockQuery (ShelleyBlock proto era) fp result) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrecIntBlockQuery (ShelleyBlock proto era) fp result → ShowS #

showBlockQuery (ShelleyBlock proto era) fp result → String #

showList ∷ [BlockQuery (ShelleyBlock proto era) fp result] → ShowS #

Eq (BlockQuery ByronBlock fp result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

(==)BlockQuery ByronBlock fp result → BlockQuery ByronBlock fp result → Bool #

(/=)BlockQuery ByronBlock fp result → BlockQuery ByronBlock fp result → Bool #

Eq (BlockQuery (ShelleyBlock proto era) fp result) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

(==)BlockQuery (ShelleyBlock proto era) fp result → BlockQuery (ShelleyBlock proto era) fp result → Bool #

(/=)BlockQuery (ShelleyBlock proto era) fp result → BlockQuery (ShelleyBlock proto era) fp result → Bool #

Inject (SomeBlockQuery :.: BlockQuery) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

data BlockQuery ByronBlock fp result Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data BlockQuery (HardForkBlock xs) footprint result 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

data BlockQuery (HardForkBlock xs) footprint result where
data BlockQuery (DualBlock m a) footprint result 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data BlockQuery (DualBlock m a) footprint result
data BlockQuery (ShelleyBlock proto era) fp result Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

data BlockQuery (ShelleyBlock proto era) fp result where

data StakeSnapshot Source #

The stake snapshot returns information about the mark, set, go ledger snapshots for a pool, plus the total active stake for each snapshot that can be used in a sigma calculation.

Each snapshot is taken at the end of a different era. The go snapshot is the current one and was taken two epochs earlier, set was taken one epoch ago, and mark was taken immediately before the start of the current epoch.

Constructors

StakeSnapshot 

Fields

Instances

Instances details
FromCBOR StakeSnapshot Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

ToCBOR StakeSnapshot Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

NFData StakeSnapshot Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnfStakeSnapshot → () #

Generic StakeSnapshot Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Associated Types

type Rep StakeSnapshot 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep StakeSnapshot = D1 ('MetaData "StakeSnapshot" "Ouroboros.Consensus.Shelley.Ledger.Query" "ouroboros-consensus-cardano-0.24.0.0-inplace" 'False) (C1 ('MetaCons "StakeSnapshot" 'PrefixI 'True) (S1 ('MetaSel ('Just "ssMarkPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: (S1 ('MetaSel ('Just "ssSetPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "ssGoPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))
Show StakeSnapshot Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Eq StakeSnapshot Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep StakeSnapshot Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep StakeSnapshot = D1 ('MetaData "StakeSnapshot" "Ouroboros.Consensus.Shelley.Ledger.Query" "ouroboros-consensus-cardano-0.24.0.0-inplace" 'False) (C1 ('MetaCons "StakeSnapshot" 'PrefixI 'True) (S1 ('MetaSel ('Just "ssMarkPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: (S1 ('MetaSel ('Just "ssSetPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "ssGoPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))

data StakeSnapshots Source #

Instances

Instances details
FromCBOR StakeSnapshots Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

ToCBOR StakeSnapshots Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

NFData StakeSnapshots Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnfStakeSnapshots → () #

Generic StakeSnapshots Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Associated Types

type Rep StakeSnapshots 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep StakeSnapshots = D1 ('MetaData "StakeSnapshots" "Ouroboros.Consensus.Shelley.Ledger.Query" "ouroboros-consensus-cardano-0.24.0.0-inplace" 'False) (C1 ('MetaCons "StakeSnapshots" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ssStakeSnapshots") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool) StakeSnapshot)) :*: S1 ('MetaSel ('Just "ssMarkTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin)) :*: (S1 ('MetaSel ('Just "ssSetTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "ssGoTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))
Show StakeSnapshots Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Eq StakeSnapshots Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep StakeSnapshots Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep StakeSnapshots = D1 ('MetaData "StakeSnapshots" "Ouroboros.Consensus.Shelley.Ledger.Query" "ouroboros-consensus-cardano-0.24.0.0-inplace" 'False) (C1 ('MetaCons "StakeSnapshots" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ssStakeSnapshots") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool) StakeSnapshot)) :*: S1 ('MetaSel ('Just "ssMarkTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin)) :*: (S1 ('MetaSel ('Just "ssSetTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "ssGoTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))

Serialisation

decodeShelleyResult ∷ ∀ proto era (fp ∷ QueryFootprint) result. ShelleyCompatible proto era ⇒ ShelleyNodeToClientVersionBlockQuery (ShelleyBlock proto era) fp result → ∀ s. Decoder s result Source #

encodeShelleyQuery ∷ ∀ era proto (fp ∷ QueryFootprint) result. ShelleyBasedEra era ⇒ BlockQuery (ShelleyBlock proto era) fp result → Encoding Source #

encodeShelleyResult ∷ ∀ proto era (fp ∷ QueryFootprint) result. ShelleyCompatible proto era ⇒ ShelleyNodeToClientVersionBlockQuery (ShelleyBlock proto era) fp result → result → Encoding Source #

BlockSupportsHFLedgerQuery instances

answerShelleyLookupQueries Source #

Arguments

∷ ∀ proto era m result blk. (Monad m, ShelleyCompatible proto era) 
⇒ (LedgerTables (LedgerState (ShelleyBlock proto era)) KeysMKLedgerTables (LedgerState blk) KeysMK)

Inject ledger tables

→ (TxOut (LedgerState blk) → TxOut era)

Eject TxOut

→ (TxIn (LedgerState blk) → TxIn)

Eject TxIn

ExtLedgerCfg (ShelleyBlock proto era) 
BlockQuery (ShelleyBlock proto era) 'QFLookupTables result 
ReadOnlyForker' m blk 
→ m result 

answerShelleyTraversingQueries Source #

Arguments

∷ ∀ proto era m result blk. (ShelleyCompatible proto era, Ord (TxIn (LedgerState blk)), Eq (TxOut (LedgerState blk)), MemPack (TxOut (LedgerState blk)), IndexedMemPack (LedgerState blk EmptyMK) (TxOut (LedgerState blk)), MemPack (TxIn (LedgerState blk)), Monad m) 
⇒ (TxOut (LedgerState blk) → TxOut era)

Eject TxOut

→ (TxIn (LedgerState blk) → TxIn)

Eject TxIn

→ (∀ result'. BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result' → TxOut (LedgerState blk) → Bool)

Get filter by query

ExtLedgerCfg (ShelleyBlock proto era) 
BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result 
ReadOnlyForker' m blk 
→ m result 

shelleyQFTraverseTablesPredicate ∷ ∀ proto era proto' era' result. (ShelleyBasedEra era, ShelleyBasedEra era') ⇒ BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result → TxOut (LedgerState (ShelleyBlock proto' era')) → Bool Source #

Orphan instances

SameDepIndex2 (BlockQuery (ShelleyBlock proto era) ∷ QueryFootprintTypeType) Source # 
Instance details

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery (ShelleyBlock proto era) x a → BlockQuery (ShelleyBlock proto era) y b → Maybe ('(x, a) :~: '(y, b)) Source #

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era), ProtoCrypto proto ~ crypto, Crypto crypto) ⇒ BlockSupportsLedgerQuery (ShelleyBlock proto era) Source # 
Instance details

Methods

answerPureBlockQueryExtLedgerCfg (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) 'QFNoTables result → ExtLedgerState (ShelleyBlock proto era) EmptyMK → result Source #

answerBlockQueryLookupMonadSTM m ⇒ ExtLedgerCfg (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) 'QFLookupTables result → ReadOnlyForker' m (ShelleyBlock proto era) → m result Source #

answerBlockQueryTraverseMonadSTM m ⇒ ExtLedgerCfg (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result → ReadOnlyForker' m (ShelleyBlock proto era) → m result Source #

blockQueryIsSupportedOnVersion ∷ ∀ (fp ∷ QueryFootprint) result. BlockQuery (ShelleyBlock proto era) fp result → BlockNodeToClientVersion (ShelleyBlock proto era) → Bool Source #

ShelleyCompatible proto era ⇒ ShowQuery (BlockQuery (ShelleyBlock proto era) fp) Source # 
Instance details

Methods

showResultBlockQuery (ShelleyBlock proto era) fp result → result → String Source #

(Typeable era, Typeable proto) ⇒ ShowProxy (BlockQuery (ShelleyBlock proto era) ∷ QueryFootprintTypeType) Source # 
Instance details

Methods

showProxyProxy (BlockQuery (ShelleyBlock proto era)) → String Source #

Show (BlockQuery (ShelleyBlock proto era) fp result) Source # 
Instance details

Methods

showsPrecIntBlockQuery (ShelleyBlock proto era) fp result → ShowS #

showBlockQuery (ShelleyBlock proto era) fp result → String #

showList ∷ [BlockQuery (ShelleyBlock proto era) fp result] → ShowS #

Eq (BlockQuery (ShelleyBlock proto era) fp result) Source # 
Instance details

Methods

(==)BlockQuery (ShelleyBlock proto era) fp result → BlockQuery (ShelleyBlock proto era) fp result → Bool #

(/=)BlockQuery (ShelleyBlock proto era) fp result → BlockQuery (ShelleyBlock proto era) fp result → Bool #