ouroboros-consensus-shelley-0.4.0.0: Shelley ledger integration in the Ouroboros consensus layer
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.Shelley.Ledger

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

data family GenTx blk Source #

Generalized transaction

The mempool (and, accordingly, blocks) consist of "generalized transactions"; this could be "proper" transactions (transferring funds) but also other kinds of things such as update proposals, delegations, etc.

Instances

Instances details
(Typeable era, Typeable proto) ⇒ ShowProxy (GenTx (ShelleyBlock proto era) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

(Typeable era, Typeable proto) ⇒ ShowProxy (TxId (GenTx (ShelleyBlock proto era)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (TxId (GenTx (ShelleyBlock proto era))) → String Source #

(Typeable era, Typeable proto) ⇒ ShowProxy (Validated (GenTx (ShelleyBlock proto era)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (Validated (GenTx (ShelleyBlock proto era))) → String Source #

(ShelleyBasedEra era, TranslateEra era WrapTx) ⇒ TranslateEra era (GenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (GenTx :.: ShelleyBlock proto)

Methods

translateEra ∷ TranslationContext era → (GenTx :.: ShelleyBlock proto) (PreviousEra era) → Except (TranslationError era (GenTx :.: ShelleyBlock proto)) ((GenTx :.: ShelleyBlock proto) era)

ShelleyBasedEra era ⇒ Eq (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==)GenTx (ShelleyBlock proto era) → GenTx (ShelleyBlock proto era) → Bool Source #

(/=)GenTx (ShelleyBlock proto era) → GenTx (ShelleyBlock proto era) → Bool Source #

Eq (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(/=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

ShelleyBasedEra era ⇒ Eq (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==)Validated (GenTx (ShelleyBlock proto era)) → Validated (GenTx (ShelleyBlock proto era)) → Bool Source #

(/=)Validated (GenTx (ShelleyBlock proto era)) → Validated (GenTx (ShelleyBlock proto era)) → Bool Source #

Ord (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

compareTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Ordering Source #

(<)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(<=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(>)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(>=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

maxTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) Source #

minTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ Show (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTx (ShelleyBlock proto era) → ShowS Source #

showGenTx (ShelleyBlock proto era) → String Source #

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

Show (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTxId (ShelleyBlock proto era) → ShowS Source #

showGenTxId (ShelleyBlock proto era) → String Source #

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

ShelleyBasedEra era ⇒ Show (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntValidated (GenTx (ShelleyBlock proto era)) → ShowS Source #

showValidated (GenTx (ShelleyBlock proto era)) → String Source #

showList ∷ [Validated (GenTx (ShelleyBlock proto era))] → ShowS Source #

Generic (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (GenTx (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromGenTx (ShelleyBlock proto era) → Rep (GenTx (ShelleyBlock proto era)) x Source #

toRep (GenTx (ShelleyBlock proto era)) x → GenTx (ShelleyBlock proto era) Source #

Generic (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (Validated (GenTx (ShelleyBlock proto era))) ∷ TypeType Source #

Methods

fromValidated (GenTx (ShelleyBlock proto era)) → Rep (Validated (GenTx (ShelleyBlock proto era))) x Source #

toRep (Validated (GenTx (ShelleyBlock proto era))) x → Validated (GenTx (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ HasTxId (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

txIdGenTx (ShelleyBlock proto era) → TxId (GenTx (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ Condense (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condenseGenTx (ShelleyBlock proto era) → String Source #

Condense (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condenseGenTxId (ShelleyBlock proto era) → String Source #

ShelleyBasedEra era ⇒ NoThunks (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks ∷ Context → GenTx (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → GenTx (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (GenTx (ShelleyBlock proto era)) → String #

NoThunks (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks ∷ Context → TxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → TxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (TxId (GenTx (ShelleyBlock proto era))) → String #

ShelleyBasedEra era ⇒ NoThunks (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks ∷ Context → Validated (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Validated (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Validated (GenTx (ShelleyBlock proto era))) → String #

ShelleyCompatible proto era ⇒ ToCBOR (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

toCBORGenTx (ShelleyBlock proto era) → Encoding

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (GenTx (ShelleyBlock proto era)) → Size

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [GenTx (ShelleyBlock proto era)] → Size

(Crypto (EraCrypto era), Typeable era, Typeable proto) ⇒ DecCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

decCBOR ∷ Decoder s (TxId (GenTx (ShelleyBlock proto era)))

dropCBORProxy (TxId (GenTx (ShelleyBlock proto era))) → Decoder s ()

labelProxy (TxId (GenTx (ShelleyBlock proto era))) → Text

(Crypto (EraCrypto era), Typeable era, Typeable proto) ⇒ EncCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

encCBORTxId (GenTx (ShelleyBlock proto era)) → Encoding

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (TxId (GenTx (ShelleyBlock proto era))) → Size

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [TxId (GenTx (ShelleyBlock proto era))] → Size

ShelleyCompatible proto era ⇒ FromCBOR (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

fromCBOR ∷ Decoder s (GenTx (ShelleyBlock proto era))

labelProxy (GenTx (ShelleyBlock proto era)) → Text

ShelleyCompatible proto era ⇒ SerialiseNodeToNode (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNodeCodecConfig (ShelleyBlock proto era) → BlockNodeToNodeVersion (ShelleyBlock proto era) → GenTxId (ShelleyBlock proto era) → Encoding Source #

decodeNodeToNodeCodecConfig (ShelleyBlock proto era) → BlockNodeToNodeVersion (ShelleyBlock proto era) → ∀ s. Decoder s (GenTxId (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ SerialiseNodeToNode (ShelleyBlock proto era) (GenTx (ShelleyBlock proto era)) Source #

The To/FromCBOR instances defined in cardano-ledger use CBOR-in-CBOR to get the annotation.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNodeCodecConfig (ShelleyBlock proto era) → BlockNodeToNodeVersion (ShelleyBlock proto era) → GenTx (ShelleyBlock proto era) → Encoding Source #

decodeNodeToNodeCodecConfig (ShelleyBlock proto era) → BlockNodeToNodeVersion (ShelleyBlock proto era) → ∀ s. Decoder s (GenTx (ShelleyBlock proto era)) Source #

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClientCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → GenTxId (ShelleyBlock proto era) → Encoding Source #

decodeNodeToClientCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → ∀ s. Decoder s (GenTxId (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (GenTx (ShelleyBlock proto era)) Source #

Uses CBOR-in-CBOR in the To/FromCBOR instances to get the annotation.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClientCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → GenTx (ShelleyBlock proto era) → Encoding Source #

decodeNodeToClientCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → ∀ s. Decoder s (GenTx (ShelleyBlock proto era)) Source #

type TranslationError era (GenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (GenTx :.: ShelleyBlock proto) = TranslationError era WrapTx
type Rep (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs))))
type Rep (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep (GenTx (ShelleyBlock proto era)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.Shelley.Ledger.Mempool" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyTx" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId (EraCrypto era))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Tx era))))
type Rep (TxId (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
type Rep (Validated (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep (Validated (GenTx (ShelleyBlock proto era))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.Shelley.Ledger.Mempool" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyValidatedTx" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId (EraCrypto era))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Validated (Tx era)))))
newtype GenTx (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

newtype TxId (GenTx (ShelleyBlock proto era)) = ShelleyTxId (TxId (EraCrypto era))
newtype Validated (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

data Validated (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

data Validated (GenTx (ShelleyBlock proto era)) = ShelleyValidatedTx !(TxId (EraCrypto era)) !(Validated (Tx era))
data GenTx (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

data GenTx (ShelleyBlock proto era) = ShelleyTx !(TxId (EraCrypto era)) !(Tx era)

data family TxId tx Source #

A generalized transaction, GenTx, identifier.

Instances

Instances details
(Typeable era, Typeable proto) ⇒ ShowProxy (TxId (GenTx (ShelleyBlock proto era)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (TxId (GenTx (ShelleyBlock proto era))) → String Source #

Eq (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(/=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

Ord (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

compareTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Ordering Source #

(<)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(<=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(>)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(>=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

maxTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) Source #

minTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) Source #

Show (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTxId (ShelleyBlock proto era) → ShowS Source #

showGenTxId (ShelleyBlock proto era) → String Source #

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

Condense (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condenseGenTxId (ShelleyBlock proto era) → String Source #

NoThunks (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks ∷ Context → TxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → TxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (TxId (GenTx (ShelleyBlock proto era))) → String #

(Crypto (EraCrypto era), Typeable era, Typeable proto) ⇒ DecCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

decCBOR ∷ Decoder s (TxId (GenTx (ShelleyBlock proto era)))

dropCBORProxy (TxId (GenTx (ShelleyBlock proto era))) → Decoder s ()

labelProxy (TxId (GenTx (ShelleyBlock proto era))) → Text

(Crypto (EraCrypto era), Typeable era, Typeable proto) ⇒ EncCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

encCBORTxId (GenTx (ShelleyBlock proto era)) → Encoding

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (TxId (GenTx (ShelleyBlock proto era))) → Size

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [TxId (GenTx (ShelleyBlock proto era))] → Size

ShelleyCompatible proto era ⇒ SerialiseNodeToNode (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNodeCodecConfig (ShelleyBlock proto era) → BlockNodeToNodeVersion (ShelleyBlock proto era) → GenTxId (ShelleyBlock proto era) → Encoding Source #

decodeNodeToNodeCodecConfig (ShelleyBlock proto era) → BlockNodeToNodeVersion (ShelleyBlock proto era) → ∀ s. Decoder s (GenTxId (ShelleyBlock proto era)) Source #

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClientCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → GenTxId (ShelleyBlock proto era) → Encoding Source #

decodeNodeToClientCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → ∀ s. Decoder s (GenTxId (ShelleyBlock proto era)) Source #

type Rep (TxId (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
newtype TxId (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

newtype TxId (GenTx (ShelleyBlock proto era)) = ShelleyTxId (TxId (EraCrypto era))

data family Validated x Source #

" Validated " transaction or block

The ledger defines how to validate transactions and blocks. It's possible the type before and after validation may be distinct (eg Alonzo transactions), which originally motivated this family.

We also gain the related benefit that certain interface functions, such as those that reapply blocks, can have a more precise type now. TODO

Similarly, the Node-to-Client mini protocols can explicitly indicate that the client trusts the blocks from the local server, by having the server send Validated blocks to the client. TODO

Note that validation has different implications for a transaction than for a block. In particular, a validated transaction can be " reapplied " to different ledger states, whereas a validated block must only be " reapplied " to the exact same ledger state (eg as part of rebuilding from an on-disk ledger snapshot).

Since the ledger defines validation, see the ledger details for concrete examples of what determines the validity (wrt to a LedgerState) of a transaction and/or block. Example properties include: a transaction's claimed inputs exist and are still unspent, a block carries a sufficient cryptographic signature, etc.

Instances

Instances details
(Typeable era, Typeable proto) ⇒ ShowProxy (Validated (GenTx (ShelleyBlock proto era)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (Validated (GenTx (ShelleyBlock proto era))) → String Source #

ShelleyBasedEra era ⇒ Eq (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==)Validated (GenTx (ShelleyBlock proto era)) → Validated (GenTx (ShelleyBlock proto era)) → Bool Source #

(/=)Validated (GenTx (ShelleyBlock proto era)) → Validated (GenTx (ShelleyBlock proto era)) → Bool Source #

ShelleyBasedEra era ⇒ Show (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntValidated (GenTx (ShelleyBlock proto era)) → ShowS Source #

showValidated (GenTx (ShelleyBlock proto era)) → String Source #

showList ∷ [Validated (GenTx (ShelleyBlock proto era))] → ShowS Source #

Generic (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (Validated (GenTx (ShelleyBlock proto era))) ∷ TypeType Source #

Methods

fromValidated (GenTx (ShelleyBlock proto era)) → Rep (Validated (GenTx (ShelleyBlock proto era))) x Source #

toRep (Validated (GenTx (ShelleyBlock proto era))) x → Validated (GenTx (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ NoThunks (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks ∷ Context → Validated (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Validated (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Validated (GenTx (ShelleyBlock proto era))) → String #

type Rep (Validated (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep (Validated (GenTx (ShelleyBlock proto era))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.Shelley.Ledger.Mempool" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyValidatedTx" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId (EraCrypto era))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Validated (Tx era)))))
newtype Validated (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

data Validated (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

data Validated (GenTx (ShelleyBlock proto era)) = ShelleyValidatedTx !(TxId (EraCrypto era)) !(Validated (Tx era))

data family LedgerState blk Source #

Ledger state associated with a block

Instances

Instances details
(ShelleyBasedEra era, TranslateEra era (ShelleyTip proto), TranslateEra era NewEpochState, TranslationError era NewEpochState ~ Void) ⇒ TranslateEra era (LedgerState :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (LedgerState :.: ShelleyBlock proto)

Methods

translateEra ∷ TranslationContext era → (LedgerState :.: ShelleyBlock proto) (PreviousEra era) → Except (TranslationError era (LedgerState :.: ShelleyBlock proto)) ((LedgerState :.: ShelleyBlock proto) era)

CanHardFork xs ⇒ Eq (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

ShelleyBasedEra era ⇒ Eq (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

(==)LedgerState (ShelleyBlock proto era) → LedgerState (ShelleyBlock proto era) → Bool Source #

(/=)LedgerState (ShelleyBlock proto era) → LedgerState (ShelleyBlock proto era) → Bool Source #

CanHardFork xs ⇒ Show (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

ShelleyBasedEra era ⇒ Show (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

showsPrecIntLedgerState (ShelleyBlock proto era) → ShowS Source #

showLedgerState (ShelleyBlock proto era) → String Source #

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

Generic (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (LedgerState (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromLedgerState (ShelleyBlock proto era) → Rep (LedgerState (ShelleyBlock proto era)) x Source #

toRep (LedgerState (ShelleyBlock proto era)) x → LedgerState (ShelleyBlock proto era) Source #

Generic (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) ∷ TypeType Source #

Methods

fromTicked (LedgerState (ShelleyBlock proto era)) → Rep (Ticked (LedgerState (ShelleyBlock proto era))) x Source #

toRep (Ticked (LedgerState (ShelleyBlock proto era))) x → Ticked (LedgerState (ShelleyBlock proto era)) Source #

GetTip (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTipLedgerState (ShelleyBlock proto era) → Point (LedgerState (ShelleyBlock proto era)) Source #

GetTip (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTipTicked (LedgerState (ShelleyBlock proto era)) → Point (Ticked (LedgerState (ShelleyBlock proto era))) Source #

ShelleyBasedEra era ⇒ IsLedger (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState (ShelleyBlock proto era)) Source #

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) Source #

CanHardFork xs ⇒ NoThunks (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → LedgerState (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (HardForkBlock xs)) → String #

ShelleyBasedEra era ⇒ NoThunks (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → LedgerState (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (ShelleyBlock proto era)) → String #

ShelleyBasedEra era ⇒ NoThunks (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (ShelleyBlock proto era))) → String #

ShelleyCompatible proto era ⇒ ApplyBlock (LedgerState (ShelleyBlock proto era)) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyCompatible proto era ⇒ EncodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskCodecConfig (ShelleyBlock proto era) → LedgerState (ShelleyBlock proto era) → Encoding Source #

ShelleyCompatible proto era ⇒ DecodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskCodecConfig (ShelleyBlock proto era) → ∀ s. Decoder s (LedgerState (ShelleyBlock proto era)) Source #

type TranslationError era (LedgerState :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (LedgerState :.: ShelleyBlock proto) = Void
type Rep (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (LedgerState (ShelleyBlock proto era)) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-shelley-0.4.0.0-inplace" '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 'DecidedStrict) (Rec0 ShelleyTransition))))
type Rep (Ticked (LedgerState (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.3.1.0-inplace" '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))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'False) (C1 ('MetaCons "TickedShelleyLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "untickedShelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: (S1 ('MetaSel ('Just "tickedShelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShelleyTransition) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)))))
type LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type AuxLedgerEvent (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

newtype LedgerState (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (ShelleyBlock proto era)) Source #

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type HeaderHash (LedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

data LedgerState (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data family BlockConfig blk Source #

Static configuration required to work with this type of blocks

Instances

Instances details
ShelleyBasedEra era ⇒ Show (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

showsPrecIntBlockConfig (ShelleyBlock proto era) → ShowS Source #

showBlockConfig (ShelleyBlock proto era) → String Source #

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

Generic (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (BlockConfig (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromBlockConfig (ShelleyBlock proto era) → Rep (BlockConfig (ShelleyBlock proto era)) x Source #

toRep (BlockConfig (ShelleyBlock proto era)) x → BlockConfig (ShelleyBlock proto era) Source #

CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (BlockConfig (HardForkBlock xs)) → String #

ShelleyBasedEra era ⇒ NoThunks (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks ∷ Context → BlockConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → BlockConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (BlockConfig (ShelleyBlock proto era)) → String #

type Rep (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (BlockConfig (ShelleyBlock proto era)) = D1 ('MetaData "BlockConfig" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "shelleyProtocolVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ProtVer) :*: S1 ('MetaSel ('Just "shelleySystemStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SystemStart)) :*: (S1 ('MetaSel ('Just "shelleyNetworkMagic") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetworkMagic) :*: S1 ('MetaSel ('Just "shelleyBlockIssuerVKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'BlockIssuer (EraCrypto era)) (VKey 'BlockIssuer (EraCrypto era)))))))
newtype BlockConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data BlockConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

data family CodecConfig blk Source #

Static configuration required for serialisation and deserialisation of types pertaining to this type of block.

Data family instead of type family to get better type inference.

Instances

Instances details
Generic (CodecConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (CodecConfig (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromCodecConfig (ShelleyBlock proto era) → Rep (CodecConfig (ShelleyBlock proto era)) x Source #

toRep (CodecConfig (ShelleyBlock proto era)) x → CodecConfig (ShelleyBlock proto era) Source #

CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (CodecConfig (HardForkBlock xs)) → String #

NoThunks (CodecConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks ∷ Context → CodecConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → CodecConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (CodecConfig (ShelleyBlock proto era)) → String #

type Rep (CodecConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (CodecConfig (ShelleyBlock proto era)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyCodecConfig" 'PrefixI 'False) (U1TypeType))
newtype CodecConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data CodecConfig (ShelleyBlock proto era) Source #

No particular codec configuration is needed for Shelley

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

data family StorageConfig blk Source #

Config needed for the NodeInitStorage class. Defined here to avoid circular dependencies.

Instances

Instances details
Generic (StorageConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (StorageConfig (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromStorageConfig (ShelleyBlock proto era) → Rep (StorageConfig (ShelleyBlock proto era)) x Source #

toRep (StorageConfig (ShelleyBlock proto era)) x → StorageConfig (ShelleyBlock proto era) Source #

CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (StorageConfig (HardForkBlock xs)) → String #

NoThunks (StorageConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks ∷ Context → StorageConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → StorageConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (StorageConfig (ShelleyBlock proto era)) → String #

type Rep (StorageConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (StorageConfig (ShelleyBlock proto era)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyStorageConfigSlotsPerKESPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "shelleyStorageConfigSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam)))
newtype StorageConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data StorageConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

data family Header blk Source #

Instances

Instances details
(Typeable era, Typeable proto) ⇒ ShowProxy (Header (ShelleyBlock proto era) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

ShelleyBasedEra era ⇒ ReconstructNestedCtxt Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ Eq (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

(==)Header (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Bool Source #

(/=)Header (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Bool Source #

ShelleyCompatible proto era ⇒ Show (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrecIntHeader (ShelleyBlock proto era) → ShowS Source #

showHeader (ShelleyBlock proto era) → String Source #

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

Generic (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type Rep (Header (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromHeader (ShelleyBlock proto era) → Rep (Header (ShelleyBlock proto era)) x Source #

toRep (Header (ShelleyBlock proto era)) x → Header (ShelleyBlock proto era) Source #

ShelleyCompatible proto era ⇒ Condense (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condenseHeader (ShelleyBlock proto era) → String Source #

SignedHeader (ShelleyProtocolHeader proto) ⇒ SignedHeader (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

Methods

headerSignedHeader (ShelleyBlock proto era) → Signed (Header (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ NoThunks (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

noThunks ∷ Context → Header (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Header (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Header (ShelleyBlock proto era)) → String #

HasHeader blk ⇒ StandardHash (Header blk) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

ShelleyCompatible proto era ⇒ HasHeader (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderFieldsHeader (ShelleyBlock proto era) → HeaderFields (Header (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ DecCBOR (Annotator (Header (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBOR ∷ Decoder s (Annotator (Header (ShelleyBlock proto era)))

dropCBORProxy (Annotator (Header (ShelleyBlock proto era))) → Decoder s ()

labelProxy (Annotator (Header (ShelleyBlock proto era))) → Text

ShelleyCompatible proto era ⇒ EncCBOR (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBORHeader (ShelleyBlock proto era) → Encoding

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (Header (ShelleyBlock proto era)) → Size

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [Header (ShelleyBlock proto era)] → Size

ShelleyBasedEra era ⇒ EncodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDepIxCodecConfig (ShelleyBlock proto era) → SomeSecond (NestedCtxt Header) (ShelleyBlock proto era) → Encoding Source #

ShelleyCompatible proto era ⇒ EncodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDepCodecConfig (ShelleyBlock proto era) → NestedCtxt Header (ShelleyBlock proto era) a → a → Encoding Source #

ShelleyBasedEra era ⇒ DecodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDepIxCodecConfig (ShelleyBlock proto era) → Decoder s (SomeSecond (NestedCtxt Header) (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ DecodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDepCodecConfig (ShelleyBlock proto era) → NestedCtxt Header (ShelleyBlock proto era) a → ∀ s. Decoder s (ByteString → a) Source #

ShelleyCompatible proto era ⇒ SerialiseNodeToNode (ShelleyBlock proto era) (Header (ShelleyBlock proto era)) Source #

CBOR-in-CBOR to be compatible with the wrapped (Serialised) variant.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNodeCodecConfig (ShelleyBlock proto era) → BlockNodeToNodeVersion (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Encoding Source #

decodeNodeToNodeCodecConfig (ShelleyBlock proto era) → BlockNodeToNodeVersion (ShelleyBlock proto era) → ∀ s. Decoder s (Header (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ EncodeDisk (ShelleyBlock proto era) (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskCodecConfig (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Encoding Source #

ShelleyCompatible proto era ⇒ DecodeDisk (ShelleyBlock proto era) (ByteStringHeader (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskCodecConfig (ShelleyBlock proto era) → ∀ s. Decoder s (ByteStringHeader (ShelleyBlock proto era)) Source #

type Rep (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type Rep (Header (ShelleyBlock proto era)) = D1 ('MetaData "Header" "Ouroboros.Consensus.Shelley.Ledger.Block" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyHeaderRaw") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyProtocolHeader proto)) :*: S1 ('MetaSel ('Just "shelleyHeaderHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyHash (ProtoCrypto proto)))))
type BlockProtocol (Header blk) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type Signed (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

type HeaderHash (Header blk) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk) = HeaderHash blk
data Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

class HasHeader (Header blk) ⇒ GetHeader blk where Source #

Methods

getHeader ∷ blk → Header blk Source #

blockMatchesHeaderHeader blk → blk → Bool Source #

Check whether the header is the header of the block.

For example, by checking whether the hash of the body stored in the header matches that of the block.

headerIsEBBHeader blk → Maybe EpochNo Source #

When the given header is the header of an Epoch Boundary Block, returns its epoch number.

Instances

Instances details
ShelleyCompatible proto era ⇒ GetHeader (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderShelleyBlock proto era → Header (ShelleyBlock proto era) Source #

blockMatchesHeaderHeader (ShelleyBlock proto era) → ShelleyBlock proto era → Bool Source #

headerIsEBBHeader (ShelleyBlock proto era) → Maybe EpochNo Source #

data family NestedCtxt_ blk ∷ (TypeType) → TypeType Source #

Context identifying what kind of block we have

In almost all places we will use NestedCtxt rather than NestedCtxt_.

Instances

Instances details
SameDepIndex (NestedCtxt_ (ShelleyBlock proto era) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

sameDepIndexNestedCtxt_ (ShelleyBlock proto era) f a → NestedCtxt_ (ShelleyBlock proto era) f b → Maybe (a :~: b) Source #

TrivialDependency (NestedCtxt_ (ShelleyBlock proto era) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) Source #

Methods

hasSingleIndexNestedCtxt_ (ShelleyBlock proto era) f a → NestedCtxt_ (ShelleyBlock proto era) f b → a :~: b Source #

indexIsTrivialNestedCtxt_ (ShelleyBlock proto era) f (TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f)) Source #

Show (NestedCtxt_ (ShelleyBlock proto era) f a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrecIntNestedCtxt_ (ShelleyBlock proto era) f a → ShowS Source #

showNestedCtxt_ (ShelleyBlock proto era) f a → String Source #

showList ∷ [NestedCtxt_ (ShelleyBlock proto era) f a] → ShowS Source #

data NestedCtxt_ (HardForkBlock xs) a b 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

data NestedCtxt_ (HardForkBlock xs) a b where
data NestedCtxt_ (ShelleyBlock proto era) f a Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

data NestedCtxt_ (ShelleyBlock proto era) f a where
type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) = f (ShelleyBlock proto era)

data family Ticked st Source #

" Ticked " piece of state (LedgerState, LedgerView, ChainIndepState)

Ticking refers to the passage of time (the ticking of the clock). When a piece of state is marked as ticked, it means that time-related changes have been applied to the state (or forecast).

Some examples of time related changes:

  • Scheduled delegations might have been applied in Byron
  • New leader schedule computed for Shelley
  • Transition from Byron to Shelley activated in the hard fork combinator.
  • Nonces switched out at the start of a new epoch.

Instances

Instances details
Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS Source #

showTicked () → String Source #

showList ∷ [Ticked ()] → ShowS Source #

(SListI xs, Show (Ticked a)) ⇒ Show (Ticked (HardForkLedgerView_ (K a ∷ TypeType) xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

Show (Ticked a) ⇒ Show (Ticked (K a x)) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked (K a x) → ShowS Source #

showTicked (K a x) → String Source #

showList ∷ [Ticked (K a x)] → ShowS Source #

Generic (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) ∷ TypeType Source #

Methods

fromTicked (LedgerState (ShelleyBlock proto era)) → Rep (Ticked (LedgerState (ShelleyBlock proto era))) x Source #

toRep (Ticked (LedgerState (ShelleyBlock proto era))) x → Ticked (LedgerState (ShelleyBlock proto era)) Source #

IsLedger (LedgerState blk) ⇒ GetTip (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

GetTip (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTipTicked (LedgerState (ShelleyBlock proto era)) → Point (Ticked (LedgerState (ShelleyBlock proto era))) Source #

ShelleyBasedEra era ⇒ NoThunks (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (ShelleyBlock proto era))) → String #

Show (Ticked (f a)) ⇒ Show ((Ticked :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecInt → (Ticked :.: f) a → ShowS Source #

show ∷ (Ticked :.: f) a → String Source #

showList ∷ [(Ticked :.: f) a] → ShowS Source #

NoThunks (Ticked (f a)) ⇒ NoThunks ((Ticked :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

noThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

showTypeOfProxy ((Ticked :.: f) a) → String #

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

type Rep (Ticked (LedgerState (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.3.1.0-inplace" '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))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'False) (C1 ('MetaCons "TickedShelleyLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "untickedShelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: (S1 ('MetaSel ('Just "tickedShelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShelleyTransition) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)))))
data Ticked (HardForkChainDepState xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

newtype Ticked (WrapChainDepState blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

newtype Ticked (WrapLedgerView blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

data Ticked (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (ShelleyBlock proto era)) Source #

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data Ticked (PraosState c)

Ticked PraosState

Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data Ticked (TPraosState c)

Ticked TPraosState

Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

newtype Ticked (LedgerView c)

Ledger view at a particular slot

Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

newtype Ticked (LedgerView c)

Ledger view at a particular slot

Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

newtype Ticked (LedgerView c) = TickedPraosLedgerView {}
type HeaderHash (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

data Ticked (HardForkLedgerView_ f xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

newtype Ticked (K a x) 
Instance details

Defined in Ouroboros.Consensus.Ticked

newtype Ticked (K a x) = TickedK {}

newtype ApplyTxError era #

Constructors

ApplyTxError [PredicateFailure (EraRule "LEDGER" era)] 

Instances

Instances details
Eq (PredicateFailure (EraRule "LEDGER" era)) ⇒ Eq (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

(==)ApplyTxError era → ApplyTxError era → Bool Source #

(/=)ApplyTxError era → ApplyTxError era → Bool Source #

Show (PredicateFailure (EraRule "LEDGER" era)) ⇒ Show (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

(Era era, EncCBOR (PredicateFailure (EraRule "LEDGER" era))) ⇒ ToCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

toCBORApplyTxError era → Encoding

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (ApplyTxError era) → Size

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [ApplyTxError era] → Size

(Era era, DecCBOR (PredicateFailure (EraRule "LEDGER" era))) ⇒ DecCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

decCBOR ∷ Decoder s (ApplyTxError era)

dropCBORProxy (ApplyTxError era) → Decoder s ()

labelProxy (ApplyTxError era) → Text

(Era era, EncCBOR (PredicateFailure (EraRule "LEDGER" era))) ⇒ EncCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

encCBORApplyTxError era → Encoding

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (ApplyTxError era) → Size

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [ApplyTxError era] → Size

(Era era, DecCBOR (PredicateFailure (EraRule "LEDGER" era))) ⇒ FromCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

fromCBOR ∷ Decoder s (ApplyTxError era)

labelProxy (ApplyTxError era) → Text

Typeable era ⇒ ShowProxy (ApplyTxError era ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (ApplyTxError era) → String Source #

ShelleyBasedEra era ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (ApplyTxError era) Source #
ApplyTxErr '(ShelleyBlock era)'
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClientCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → ApplyTxError era → Encoding Source #

decodeNodeToClientCodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → ∀ s. Decoder s (ApplyTxError era) Source #

class (EraSegWits era, EraGovernance era, ApplyTx era, ApplyBlock era, CanStartFromGenesis era, GetLedgerView era, NoThunks (StashedAVVMAddresses era), EncCBOR (StashedAVVMAddresses era), DecCBOR (StashedAVVMAddresses era), Show (StashedAVVMAddresses era), Eq (StashedAVVMAddresses era), DecCBOR (PredicateFailure (EraRule "LEDGER" era)), EncCBOR (PredicateFailure (EraRule "LEDGER" era)), DecCBOR (PredicateFailure (EraRule "DELEGS" era)), EncCBOR (PredicateFailure (EraRule "DELEGS" era)), DecCBOR (PredicateFailure (EraRule "UTXOW" era)), EncCBOR (PredicateFailure (EraRule "UTXOW" era)), DSignable (EraCrypto era) (Hash (EraCrypto era) EraIndependentTxBody), NoThunks (PredicateFailure (EraRule "BBODY" era)), NoThunks (TranslationContext era)) ⇒ ShelleyBasedEra era Source #

Consensus often needs some more functionality than the ledger currently provides.

Either the functionality shouldn't or can't live in the ledger, in which case it can be part and remain part of ShelleyBasedEra. Or, the functionality should live in the ledger, but hasn't yet been added to the ledger, or it hasn't yet been propagated to this repository, in which case it can be added to this class until that is the case.

If this class becomes redundant, We can move it to ledger and re-export it from here.

TODO Currently we include some constraints on the update state which are needed to determine the hard fork point. In the future this should be replaced with an appropriate API - see https://github.com/input-output-hk/ouroboros-network/issues/2890

Minimal complete definition

shelleyBasedEraName, applyShelleyBasedTx

Instances

Instances details
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) ⇒ ShelleyBasedEra (AllegraEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (AllegraEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (AllegraEra c) → LedgerState (AllegraEra c) → WhetherToIntervene → Tx (AllegraEra c) → Except (ApplyTxError (AllegraEra c)) (LedgerState (AllegraEra c), Validated (Tx (AllegraEra c))) Source #

(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) ⇒ ShelleyBasedEra (ShelleyEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (ShelleyEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (ShelleyEra c) → LedgerState (ShelleyEra c) → WhetherToIntervene → Tx (ShelleyEra c) → Except (ApplyTxError (ShelleyEra c)) (LedgerState (ShelleyEra c), Validated (Tx (ShelleyEra c))) Source #

(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) ⇒ ShelleyBasedEra (AlonzoEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (AlonzoEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (AlonzoEra c) → LedgerState (AlonzoEra c) → WhetherToIntervene → Tx (AlonzoEra c) → Except (ApplyTxError (AlonzoEra c)) (LedgerState (AlonzoEra c), Validated (Tx (AlonzoEra c))) Source #

(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) ⇒ ShelleyBasedEra (MaryEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (MaryEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (MaryEra c) → LedgerState (MaryEra c) → WhetherToIntervene → Tx (MaryEra c) → Except (ApplyTxError (MaryEra c)) (LedgerState (MaryEra c), Validated (Tx (MaryEra c))) Source #

PraosCrypto c ⇒ ShelleyBasedEra (BabbageEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (BabbageEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (BabbageEra c) → LedgerState (BabbageEra c) → WhetherToIntervene → Tx (BabbageEra c) → Except (ApplyTxError (BabbageEra c)) (LedgerState (BabbageEra c), Validated (Tx (BabbageEra c))) Source #

PraosCrypto c ⇒ ShelleyBasedEra (ConwayEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (ConwayEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (ConwayEra c) → LedgerState (ConwayEra c) → WhetherToIntervene → Tx (ConwayEra c) → Except (ApplyTxError (ConwayEra c)) (LedgerState (ConwayEra c), Validated (Tx (ConwayEra c))) Source #

verifyHeaderIntegrity Source #

Arguments

ProtocolHeaderSupportsKES proto 
Word64

Slots per KES period

ShelleyProtocolHeader proto 
Bool 

Verify that the signature on a header is correct and valid.

newtype ShelleyHash crypto Source #

Constructors

ShelleyHash 

Fields

Instances

Instances details
Eq (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

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

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

Ord (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

compareShelleyHash crypto → ShelleyHash crypto → Ordering Source #

(<)ShelleyHash crypto → ShelleyHash crypto → Bool Source #

(<=)ShelleyHash crypto → ShelleyHash crypto → Bool Source #

(>)ShelleyHash crypto → ShelleyHash crypto → Bool Source #

(>=)ShelleyHash crypto → ShelleyHash crypto → Bool Source #

maxShelleyHash crypto → ShelleyHash crypto → ShelleyHash crypto Source #

minShelleyHash crypto → ShelleyHash crypto → ShelleyHash crypto Source #

Show (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

showsPrecIntShelleyHash crypto → ShowS Source #

showShelleyHash crypto → String Source #

showList ∷ [ShelleyHash crypto] → ShowS Source #

Generic (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Associated Types

type Rep (ShelleyHash crypto) ∷ TypeType Source #

Methods

fromShelleyHash crypto → Rep (ShelleyHash crypto) x Source #

toRep (ShelleyHash crypto) x → ShelleyHash crypto Source #

Crypto crypto ⇒ Serialise (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

encodeShelleyHash crypto → Encoding

decode ∷ Decoder s (ShelleyHash crypto)

encodeList ∷ [ShelleyHash crypto] → Encoding

decodeList ∷ Decoder s [ShelleyHash crypto]

Condense (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

condenseShelleyHash crypto → String Source #

NoThunks (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

noThunks ∷ Context → ShelleyHash crypto → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ShelleyHash crypto → IO (Maybe ThunkInfo) #

showTypeOfProxy (ShelleyHash crypto) → String #

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

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

toCBORShelleyHash crypto → Encoding

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

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

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

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

fromCBOR ∷ Decoder s (ShelleyHash crypto)

labelProxy (ShelleyHash crypto) → Text

type Rep (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

type Rep (ShelleyHash crypto) = D1 ('MetaData "ShelleyHash" "Ouroboros.Consensus.Shelley.Protocol.Abstract" "ouroboros-consensus-shelley-0.4.0.0-inplace" 'True) (C1 ('MetaCons "ShelleyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unShelleyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash crypto EraIndependentBlockHeader))))

data ShelleyBlock proto era Source #

Shelley-based block type.

This block is parametrised over both the (ledger) era and the protocol.

Constructors

ShelleyBlock 

Instances

Instances details
(Typeable era, Typeable proto) ⇒ ShowProxy (GenTx (ShelleyBlock proto era) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

(Typeable era, Typeable proto) ⇒ ShowProxy (TxId (GenTx (ShelleyBlock proto era)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (TxId (GenTx (ShelleyBlock proto era))) → String Source #

(Typeable era, Typeable proto) ⇒ ShowProxy (Validated (GenTx (ShelleyBlock proto era)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (Validated (GenTx (ShelleyBlock proto era))) → String Source #

(Typeable era, Typeable proto) ⇒ ShowProxy (Header (ShelleyBlock proto era) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

ShelleyBasedEra era ⇒ ReconstructNestedCtxt Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

HasNestedContent f (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

unnest ∷ f (ShelleyBlock proto era) → DepPair (NestedCtxt f (ShelleyBlock proto era)) Source #

nestDepPair (NestedCtxt f (ShelleyBlock proto era)) → f (ShelleyBlock proto era) Source #

(ShelleyBasedEra era, TranslateEra era WrapTx) ⇒ TranslateEra era (WrapValidatedGenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto)

Methods

translateEra ∷ TranslationContext era → (WrapValidatedGenTx :.: ShelleyBlock proto) (PreviousEra era) → Except (TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto)) ((WrapValidatedGenTx :.: ShelleyBlock proto) era)

(ShelleyBasedEra era, TranslateEra era WrapTx) ⇒ TranslateEra era (GenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (GenTx :.: ShelleyBlock proto)

Methods

translateEra ∷ TranslationContext era → (GenTx :.: ShelleyBlock proto) (PreviousEra era) → Except (TranslationError era (GenTx :.: ShelleyBlock proto)) ((GenTx :.: ShelleyBlock proto) era)

(ShelleyBasedEra era, TranslateEra era (ShelleyTip proto), TranslateEra era NewEpochState, TranslationError era NewEpochState ~ Void) ⇒ TranslateEra era (LedgerState :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (LedgerState :.: ShelleyBlock proto)

Methods

translateEra ∷ TranslationContext era → (LedgerState :.: ShelleyBlock proto) (PreviousEra era) → Except (TranslationError era (LedgerState :.: ShelleyBlock proto)) ((LedgerState :.: ShelleyBlock proto) era)

ShelleyBasedEra era ⇒ Eq (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==)GenTx (ShelleyBlock proto era) → GenTx (ShelleyBlock proto era) → Bool Source #

(/=)GenTx (ShelleyBlock proto era) → GenTx (ShelleyBlock proto era) → Bool Source #

Eq (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(/=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

ShelleyBasedEra era ⇒ Eq (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==)Validated (GenTx (ShelleyBlock proto era)) → Validated (GenTx (ShelleyBlock proto era)) → Bool Source #

(/=)Validated (GenTx (ShelleyBlock proto era)) → Validated (GenTx (ShelleyBlock proto era)) → Bool Source #

ShelleyBasedEra era ⇒ Eq (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

(==)LedgerState (ShelleyBlock proto era) → LedgerState (ShelleyBlock proto era) → Bool Source #

(/=)LedgerState (ShelleyBlock proto era) → LedgerState (ShelleyBlock proto era) → Bool Source #

ShelleyCompatible proto era ⇒ Eq (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

(==)Header (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Bool Source #

(/=)Header (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Bool Source #

Ord (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

compareTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Ordering Source #

(<)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(<=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(>)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

(>=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool Source #

maxTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) Source #

minTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ Show (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTx (ShelleyBlock proto era) → ShowS Source #

showGenTx (ShelleyBlock proto era) → String Source #

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

Show (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTxId (ShelleyBlock proto era) → ShowS Source #

showGenTxId (ShelleyBlock proto era) → String Source #

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

ShelleyBasedEra era ⇒ Show (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntValidated (GenTx (ShelleyBlock proto era)) → ShowS Source #

showValidated (GenTx (ShelleyBlock proto era)) → String Source #

showList ∷ [Validated (GenTx (ShelleyBlock proto era))] → ShowS Source #

ShelleyBasedEra era ⇒ Show (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

showsPrecIntLedgerState (ShelleyBlock proto era) → ShowS Source #

showLedgerState (ShelleyBlock proto era) → String Source #

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

ShelleyBasedEra era ⇒ Show (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

showsPrecIntBlockConfig (ShelleyBlock proto era) → ShowS Source #

showBlockConfig (ShelleyBlock proto era) → String Source #

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

ShelleyCompatible proto era ⇒ Show (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrecIntHeader (ShelleyBlock proto era) → ShowS Source #

showHeader (ShelleyBlock proto era) → String Source #

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

Generic (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (GenTx (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromGenTx (ShelleyBlock proto era) → Rep (GenTx (ShelleyBlock proto era)) x Source #

toRep (GenTx (ShelleyBlock proto era)) x → GenTx (ShelleyBlock proto era) Source #

Generic (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (Validated (GenTx (ShelleyBlock proto era))) ∷ TypeType Source #

Methods

fromValidated (GenTx (ShelleyBlock proto era)) → Rep (Validated (GenTx (ShelleyBlock proto era))) x Source #

toRep (Validated (GenTx (ShelleyBlock proto era))) x → Validated (GenTx (ShelleyBlock proto era)) Source #

Generic (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (LedgerState (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromLedgerState (ShelleyBlock proto era) → Rep (LedgerState (ShelleyBlock proto era)) x Source #

toRep (LedgerState (ShelleyBlock proto era)) x → LedgerState (ShelleyBlock proto era) Source #

Generic (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (BlockConfig (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromBlockConfig (ShelleyBlock proto era) → Rep (BlockConfig (ShelleyBlock proto era)) x Source #

toRep (BlockConfig (ShelleyBlock proto era)) x → BlockConfig (ShelleyBlock proto era) Source #

Generic (CodecConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (CodecConfig (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromCodecConfig (ShelleyBlock proto era) → Rep (CodecConfig (ShelleyBlock proto era)) x Source #

toRep (CodecConfig (ShelleyBlock proto era)) x → CodecConfig (ShelleyBlock proto era) Source #

Generic (StorageConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (StorageConfig (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromStorageConfig (ShelleyBlock proto era) → Rep (StorageConfig (ShelleyBlock proto era)) x Source #

toRep (StorageConfig (ShelleyBlock proto era)) x → StorageConfig (ShelleyBlock proto era) Source #

Generic (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type Rep (Header (ShelleyBlock proto era)) ∷ TypeType Source #

Methods

fromHeader (ShelleyBlock proto era) → Rep (Header (ShelleyBlock proto era)) x Source #

toRep (Header (ShelleyBlock proto era)) x → Header (ShelleyBlock proto era) Source #

Generic (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) ∷ TypeType Source #

Methods

fromTicked (LedgerState (ShelleyBlock proto era)) → Rep (Ticked (LedgerState (ShelleyBlock proto era))) x Source #

toRep (Ticked (LedgerState (ShelleyBlock proto era))) x → Ticked (LedgerState (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ HasTxId (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

txIdGenTx (ShelleyBlock proto era) → TxId (GenTx (ShelleyBlock proto era)) Source #

GetTip (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTipLedgerState (ShelleyBlock proto era) → Point (LedgerState (ShelleyBlock proto era)) Source #

GetTip (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTipTicked (LedgerState (ShelleyBlock proto era)) → Point (Ticked (LedgerState (ShelleyBlock proto era))) Source #

ShelleyBasedEra era ⇒ IsLedger (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState (ShelleyBlock proto era)) Source #

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ Condense (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condenseGenTx (ShelleyBlock proto era) → String Source #

Condense (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condenseGenTxId (ShelleyBlock proto era) → String Source #

ShelleyCompatible proto era ⇒ Condense (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condenseHeader (ShelleyBlock proto era) → String Source #

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 #

SignedHeader (ShelleyProtocolHeader proto) ⇒ SignedHeader (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

Methods

headerSignedHeader (ShelleyBlock proto era) → Signed (Header (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ NoThunks (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks ∷ Context → GenTx (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → GenTx (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (GenTx (ShelleyBlock proto era)) → String #

NoThunks (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks ∷ Context → TxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → TxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (TxId (GenTx (ShelleyBlock proto era))) → String #

ShelleyBasedEra era ⇒ NoThunks (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks ∷ Context → Validated (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Validated (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Validated (GenTx (ShelleyBlock proto era))) → String #

ShelleyBasedEra era ⇒ NoThunks (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → LedgerState (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (ShelleyBlock proto era)) → String #

ShelleyBasedEra era ⇒ NoThunks (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks ∷ Context → BlockConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → BlockConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (BlockConfig (ShelleyBlock proto era)) → String #

NoThunks (CodecConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks ∷ Context → CodecConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → CodecConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (CodecConfig (ShelleyBlock proto era)) → String #

NoThunks (StorageConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks ∷ Context → StorageConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → StorageConfig (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (StorageConfig (ShelleyBlock proto era)) → String #

ShelleyCompatible proto era ⇒ NoThunks (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

noThunks ∷ Context → Header (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Header (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Header (ShelleyBlock proto era)) → String #

ShelleyBasedEra era ⇒ NoThunks (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (ShelleyBlock proto era))) → String #

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 #

ShelleyCompatible proto era ⇒ HasHeader (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderFieldsHeader (ShelleyBlock proto era) → HeaderFields (Header (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ ToCBOR (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

toCBORGenTx (ShelleyBlock proto era) → Encoding

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (GenTx (ShelleyBlock proto era)) → Size

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [GenTx (ShelleyBlock proto era)] → Size

(Crypto (EraCrypto era), Typeable era, Typeable proto) ⇒ DecCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

decCBOR ∷ Decoder s (TxId (GenTx (ShelleyBlock proto era)))

dropCBORProxy (TxId (GenTx (ShelleyBlock proto era))) → Decoder s ()

labelProxy (TxId (GenTx (ShelleyBlock proto era))) → Text

ShelleyCompatible proto era ⇒ DecCBOR (Annotator (Header (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBOR ∷ Decoder s (Annotator (Header (ShelleyBlock proto era)))

dropCBORProxy (Annotator (Header (ShelleyBlock proto era))) → Decoder s ()

labelProxy (Annotator (Header (ShelleyBlock proto era))) → Text

ShelleyCompatible proto era ⇒ DecCBOR (Annotator (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBOR ∷ Decoder s (Annotator (ShelleyBlock proto era))

dropCBORProxy (Annotator (ShelleyBlock proto era)) → Decoder s ()

labelProxy (Annotator (ShelleyBlock proto era)) → Text

(Crypto (EraCrypto era), Typeable era, Typeable proto) ⇒ EncCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

encCBORTxId (GenTx (ShelleyBlock proto era)) → Encoding

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (TxId (GenTx (ShelleyBlock proto era))) → Size

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [TxId (GenTx (ShelleyBlock proto era))] → Size

ShelleyCompatible proto era ⇒ EncCBOR (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBORHeader (ShelleyBlock proto era) → Encoding

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (Header (ShelleyBlock proto era)) → Size

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [Header (ShelleyBlock proto era)] → Size

ShelleyCompatible proto era ⇒ FromCBOR (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

fromCBOR ∷ Decoder s (GenTx (ShelleyBlock proto era))

labelProxy (GenTx (ShelleyBlock proto era)) → Text

ShelleyBasedEra era ⇒ EncodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDepIxCodecConfig (ShelleyBlock proto era) → SomeSecond (NestedCtxt Header) (ShelleyBlock proto era) → Encoding Source #

ShelleyCompatible proto era ⇒ EncodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDepCodecConfig (ShelleyBlock proto era) → NestedCtxt Header (ShelleyBlock proto era) a → a → Encoding Source #

ShelleyBasedEra era ⇒ DecodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDepIxCodecConfig (ShelleyBlock proto era) → Decoder s (SomeSecond (NestedCtxt Header) (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ DecodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDepCodecConfig (ShelleyBlock proto era) → NestedCtxt Header (ShelleyBlock proto era) a → ∀ s. Decoder s (ByteString → a) Source #

ShelleyCompatible proto era ⇒ ApplyBlock (LedgerState (ShelleyBlock proto era)) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showProxyProxy (ShelleyBlock proto era) → 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 #

ShelleyCompatible proto era ⇒ Eq (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

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

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 #

ShelleyCompatible proto era ⇒ Show (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrecIntShelleyBlock proto era → ShowS Source #

showShelleyBlock proto era → String Source #

showList ∷ [ShelleyBlock proto era] → ShowS Source #

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) ⇒ SerialiseConstraintsHFC (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

ShelleyCompatible proto era ⇒ SerialiseNodeToNodeConstraints (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ SerialiseNodeToClientConstraints (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) ⇒ RunNode (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node

ShelleyCompatible proto era ⇒ SerialiseDiskConstraints (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) ⇒ NoHardForks (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) ⇒ SingleEraBlock (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

ShelleyCompatible proto era ⇒