ouroboros-consensus-shelley-0.4.0.0: Shelley ledger integration in the Ouroboros consensus layer
Safe HaskellNone
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
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 #

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 #

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 Source #

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

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

Defined in Ouroboros.Consensus.Ledger.Query

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrecIntBlockQuery (ShelleyBlock proto era) result → ShowS Source #

showBlockQuery (ShelleyBlock proto era) result → String Source #

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

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

Defined in Ouroboros.Consensus.Ledger.Query

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 #

(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

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

newtype NonMyopicMemberRewards c Source #

Constructors

NonMyopicMemberRewards 

Fields

Instances

Instances details
Eq (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Show (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Crypto c ⇒ ToCBOR (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBORNonMyopicMemberRewards c → Encoding

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (NonMyopicMemberRewards c) → Size

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [NonMyopicMemberRewards c] → Size

Crypto c ⇒ FromCBOR (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

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

Show (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrecIntStakeSnapshot crypto → ShowS Source #

showStakeSnapshot crypto → String Source #

showList ∷ [StakeSnapshot crypto] → ShowS Source #

Generic (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Associated Types

type Rep (StakeSnapshot crypto) ∷ TypeType Source #

Methods

fromStakeSnapshot crypto → Rep (StakeSnapshot crypto) x Source #

toRep (StakeSnapshot crypto) x → StakeSnapshot crypto Source #

NFData (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnfStakeSnapshot crypto → () Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBORStakeSnapshot crypto → Encoding

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR ∷ Decoder s (StakeSnapshot crypto)

labelProxy (StakeSnapshot crypto) → Text

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-shelley-0.4.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
Eq (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

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

Show (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrecIntStakeSnapshots crypto → ShowS Source #

showStakeSnapshots crypto → String Source #

showList ∷ [StakeSnapshots crypto] → ShowS Source #

Generic (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Associated Types

type Rep (StakeSnapshots crypto) ∷ TypeType Source #

Methods

fromStakeSnapshots crypto → Rep (StakeSnapshots crypto) x Source #

toRep (StakeSnapshots crypto) x → StakeSnapshots crypto Source #

NFData (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnfStakeSnapshots crypto → () Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBORStakeSnapshots crypto → Encoding

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR ∷ Decoder s (StakeSnapshots crypto)

labelProxy (StakeSnapshots crypto) → Text

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-shelley-0.4.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 ⇒ BlockQuery (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 ⇒ BlockQuery (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 #

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

Methods

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

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

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

Methods

showsPrecIntBlockQuery (ShelleyBlock proto era) result → ShowS Source #

showBlockQuery (ShelleyBlock proto era) result → String Source #

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

(ShelleyCompatible proto era, ProtoCrypto proto ~ crypto) ⇒ QueryLedger (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 #