ouroboros-consensus-cardano-0.12.1.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 :: Type -> Type #

Instances

Instances details
SerialiseResult ByronBlock (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeResult :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> BlockQuery ByronBlock result -> result -> Encoding

decodeResult :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> BlockQuery ByronBlock result -> forall s. Decoder s result

SerialiseNodeToClient ByronBlock (SomeSecond BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> SomeSecond BlockQuery ByronBlock -> Encoding

decodeNodeToClient :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> forall s. Decoder s (SomeSecond BlockQuery ByronBlock)

Inject (SomeSecond BlockQuery) 
Instance details

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

Methods

inject :: forall x (xs :: [Type]). CanHardFork xs => Exactly xs Bound -> Index xs x -> SomeSecond BlockQuery x -> SomeSecond BlockQuery (HardForkBlock xs)

SameDepIndex (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

SameDepIndex (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

sameDepIndex :: BlockQuery (ShelleyBlock proto era) a -> BlockQuery (ShelleyBlock proto era) b -> Maybe (a :~: b)

ShowQuery (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

showResult :: BlockQuery ByronBlock result -> result -> String

ShelleyCompatible proto era => ShowQuery (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showResult :: BlockQuery (ShelleyBlock proto era) result -> result -> String

Show (BlockQuery ByronBlock result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrec :: Int -> BlockQuery (ShelleyBlock proto era) result -> ShowS Source #

show :: BlockQuery (ShelleyBlock proto era) result -> String Source #

showList :: [BlockQuery (ShelleyBlock proto era) result] -> ShowS Source #

(forall result. Show (BlockQuery blk result)) => Show (SomeSecond BlockQuery blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

Methods

showsPrec :: Int -> SomeSecond BlockQuery blk -> ShowS Source #

show :: SomeSecond BlockQuery blk -> String Source #

showList :: [SomeSecond BlockQuery blk] -> ShowS Source #

Eq (BlockQuery ByronBlock result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Methods

(==) :: SomeSecond BlockQuery blk -> SomeSecond BlockQuery blk -> Bool Source #

(/=) :: SomeSecond BlockQuery blk -> SomeSecond BlockQuery blk -> Bool Source #

ShelleyCompatible proto era => SerialiseResult (ShelleyBlock proto era) (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeResult :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding

decodeResult :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> forall s. Decoder s result

ShowProxy (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

(Typeable era, Typeable proto) => ShowProxy (BlockQuery (ShelleyBlock proto era) :: Type -> Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showProxy :: Proxy (BlockQuery (ShelleyBlock proto era)) -> String

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (SomeSecond BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> SomeSecond BlockQuery (ShelleyBlock proto era) -> Encoding

decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))

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

newtype NonMyopicMemberRewards c Source #

Constructors

NonMyopicMemberRewards 

Fields

Instances

Instances details
Show (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Crypto c => FromCBOR (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR :: Decoder s (NonMyopicMemberRewards c)

label :: Proxy (NonMyopicMemberRewards c) -> Text

Crypto c => ToCBOR (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBOR :: NonMyopicMemberRewards c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (NonMyopicMemberRewards c) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NonMyopicMemberRewards c] -> Size

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Associated Types

type Rep (StakeSnapshot crypto) :: Type -> Type Source #

Methods

from :: StakeSnapshot crypto -> Rep (StakeSnapshot crypto) x Source #

to :: Rep (StakeSnapshot crypto) x -> StakeSnapshot crypto Source #

Show (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Crypto crypto => FromCBOR (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR :: Decoder s (StakeSnapshot crypto)

label :: Proxy (StakeSnapshot crypto) -> Text

Crypto crypto => ToCBOR (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBOR :: StakeSnapshot crypto -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StakeSnapshot crypto) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StakeSnapshot crypto] -> Size

NFData (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnf :: StakeSnapshot crypto -> () Source #

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 #

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.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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) :: Type -> Type Source #

Methods

from :: StakeSnapshots crypto -> Rep (StakeSnapshots crypto) x Source #

to :: Rep (StakeSnapshots crypto) x -> StakeSnapshots crypto Source #

Show (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Crypto crypto => FromCBOR (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR :: Decoder s (StakeSnapshots crypto)

label :: Proxy (StakeSnapshots crypto) -> Text

Crypto crypto => ToCBOR (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBOR :: StakeSnapshots crypto -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StakeSnapshots crypto) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StakeSnapshots crypto] -> Size

NFData (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnf :: StakeSnapshots crypto -> () Source #

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 #

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.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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))))

querySupportedVersion :: BlockQuery (ShelleyBlock proto era) result -> ShelleyNodeToClientVersion -> Bool Source #

Is the given query supported by the given ShelleyNodeToClientVersion?

Serialisation

decodeShelleyQuery :: forall era proto. ShelleyBasedEra era => forall s. Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)) Source #

decodeShelleyResult :: forall proto era result. ShelleyCompatible proto era => ShelleyNodeToClientVersion -> BlockQuery (ShelleyBlock proto era) result -> forall s. Decoder s result Source #

encodeShelleyQuery :: forall era proto result. ShelleyBasedEra era => BlockQuery (ShelleyBlock proto era) result -> Encoding Source #

encodeShelleyResult :: forall proto era result. ShelleyCompatible proto era => ShelleyNodeToClientVersion -> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding Source #

Orphan instances

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

Methods

sameDepIndex :: BlockQuery (ShelleyBlock proto era) a -> BlockQuery (ShelleyBlock proto era) b -> Maybe (a :~: b)

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

Methods

showResult :: BlockQuery (ShelleyBlock proto era) result -> result -> String

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

Methods

showsPrec :: Int -> BlockQuery (ShelleyBlock proto era) result -> ShowS Source #

show :: BlockQuery (ShelleyBlock proto era) result -> String Source #

showList :: [BlockQuery (ShelleyBlock proto era) result] -> ShowS 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 #

(ShelleyCompatible proto era, ProtoCrypto proto ~ crypto) => QueryLedger (ShelleyBlock proto era) Source # 
Instance details

Methods

answerBlockQuery :: ExtLedgerCfg (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> ExtLedgerState (ShelleyBlock proto era) -> result

(Typeable era, Typeable proto) => ShowProxy (BlockQuery (ShelleyBlock proto era) :: Type -> Type) Source # 
Instance details

Methods

showProxy :: Proxy (BlockQuery (ShelleyBlock proto era)) -> String