ouroboros-consensus-cardano-0.16.0.0: The instantation of the Ouroboros consensus layer used by Cardano
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Shelley.Ledger.Query

Synopsis

Documentation

data family BlockQuery blk ∷ TypeType Source #

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

Instances

Instances details
SerialiseResult ByronBlock (BlockQuery ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

SerialiseNodeToClient ByronBlock (SomeSecond BlockQuery ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

SameDepIndex (BlockQuery ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

SameDepIndex (BlockQuery (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

sameDepIndexBlockQuery (ShelleyBlock proto era) a → BlockQuery (ShelleyBlock proto era) b → Maybe (a :~: b) Source #

ShowQuery (BlockQuery ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

showResultBlockQuery ByronBlock result → result → String Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

Show (BlockQuery ByronBlock result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

showsPrecIntBlockQuery ByronBlock result → ShowS #

showBlockQuery ByronBlock result → String #

showList ∷ [BlockQuery ByronBlock result] → ShowS #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrecIntBlockQuery (ShelleyBlock proto era) result → ShowS #

showBlockQuery (ShelleyBlock proto era) result → String #

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

Eq (BlockQuery ByronBlock result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeResultCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) result → result → Encoding Source #

decodeResultCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) result → ∀ s. Decoder s result Source #

ShowProxy (BlockQuery ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Inject (SomeSecond BlockQuery) 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → SomeSecond BlockQuery x → SomeSecond BlockQuery (HardForkBlock xs) Source #

(∀ result. Show (BlockQuery blk result)) ⇒ Show (SomeSecond BlockQuery blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

SameDepIndex (BlockQuery blk) ⇒ Eq (SomeSecond BlockQuery blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

data BlockQuery ByronBlock a Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data BlockQuery (HardForkBlock xs) a 
Instance details

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

data BlockQuery (HardForkBlock xs) a where
data BlockQuery (ShelleyBlock proto era) a Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

data BlockQuery (ShelleyBlock proto era) a where

data StakeSnapshot crypto 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
Generic (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Associated Types

type Rep (StakeSnapshot crypto) ∷ TypeType #

Methods

fromStakeSnapshot crypto → Rep (StakeSnapshot crypto) x #

toRep (StakeSnapshot crypto) x → StakeSnapshot crypto #

Show (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrecIntStakeSnapshot crypto → ShowS #

showStakeSnapshot crypto → String #

showList ∷ [StakeSnapshot crypto] → ShowS #

Crypto crypto ⇒ FromCBOR (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBORDecoder s (StakeSnapshot crypto) Source #

labelProxy (StakeSnapshot crypto) → Text Source #

Crypto crypto ⇒ ToCBOR (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBORStakeSnapshot crypto → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (StakeSnapshot crypto) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [StakeSnapshot crypto] → Size Source #

NFData (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnfStakeSnapshot crypto → () #

Eq (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

(==)StakeSnapshot crypto → StakeSnapshot crypto → Bool #

(/=)StakeSnapshot crypto → StakeSnapshot crypto → Bool #

type Rep (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep (StakeSnapshot crypto) = D1 ('MetaData "StakeSnapshot" "Ouroboros.Consensus.Shelley.Ledger.Query" "ouroboros-consensus-cardano-0.16.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 crypto Source #

Constructors

StakeSnapshots 

Fields

Instances

Instances details
Generic (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Associated Types

type Rep (StakeSnapshots crypto) ∷ TypeType #

Methods

fromStakeSnapshots crypto → Rep (StakeSnapshots crypto) x #

toRep (StakeSnapshots crypto) x → StakeSnapshots crypto #

Show (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrecIntStakeSnapshots crypto → ShowS #

showStakeSnapshots crypto → String #

showList ∷ [StakeSnapshots crypto] → ShowS #

Crypto crypto ⇒ FromCBOR (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBORDecoder s (StakeSnapshots crypto) Source #

labelProxy (StakeSnapshots crypto) → Text Source #

Crypto crypto ⇒ ToCBOR (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBORStakeSnapshots crypto → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (StakeSnapshots crypto) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [StakeSnapshots crypto] → Size Source #

NFData (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnfStakeSnapshots crypto → () #

Eq (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

(==)StakeSnapshots crypto → StakeSnapshots crypto → Bool #

(/=)StakeSnapshots crypto → StakeSnapshots crypto → Bool #

type Rep (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep (StakeSnapshots crypto) = D1 ('MetaData "StakeSnapshots" "Ouroboros.Consensus.Shelley.Ledger.Query" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'False) (C1 ('MetaCons "StakeSnapshots" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ssStakeSnapshots") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto))) :*: 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))))

querySupportedVersionBlockQuery (ShelleyBlock proto era) result → ShelleyNodeToClientVersionBool Source #

Is the given query supported by the given ShelleyNodeToClientVersion?

Serialisation

decodeShelleyQuery ∷ ∀ era proto. ShelleyBasedEra era ⇒ ∀ s. Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)) Source #

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

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

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

Orphan instances

SameDepIndex (BlockQuery (ShelleyBlock proto era)) Source # 
Instance details

Methods

sameDepIndexBlockQuery (ShelleyBlock proto era) a → BlockQuery (ShelleyBlock proto era) b → Maybe (a :~: b) Source #

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

Methods

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

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

Methods

showsPrecIntBlockQuery (ShelleyBlock proto era) result → ShowS #

showBlockQuery (ShelleyBlock proto era) result → String #

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

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

Methods

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

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

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

Methods

answerBlockQueryExtLedgerCfg (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) result → ExtLedgerState (ShelleyBlock proto era) → result Source #

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

Methods

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