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

Ouroboros.Consensus.Byron.Ledger.Mempool

Description

Byron mempool integration

Synopsis

Mempool integration

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
Inject GenTx 
Instance details

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

Methods

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

SerialiseNodeToClient ByronBlock (GenTx ByronBlock) Source #

No CBOR-in-CBOR, because we check for canonical encodings, which means we can use the recomputed encoding for the annotation.

Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

SerialiseNodeToClient ByronBlock (GenTxId ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

SerialiseNodeToNode ByronBlock (GenTx ByronBlock) Source #

No CBOR-in-CBOR, because we check for canonical encodings, which means we can use the recomputed encoding for the annotation.

Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

SerialiseNodeToNode ByronBlock (GenTxId ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

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

ShowProxy (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

ShowProxy (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (GenTx :.: ShelleyBlock proto) Source #

Generic (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Associated Types

type Rep (Validated (GenTx ByronBlock)) ∷ TypeType #

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 #

Methods

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

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

Generic (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Associated Types

type Rep (GenTx ByronBlock) ∷ TypeType #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

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

Methods

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

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

Show (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

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

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

Show (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTx (ShelleyBlock proto era) → ShowS #

showGenTx (ShelleyBlock proto era) → String #

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

Show (GenTxId ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTxId (ShelleyBlock proto era) → ShowS #

showGenTxId (ShelleyBlock proto era) → String #

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

fromCBORDecoder s (GenTx (ShelleyBlock proto era)) Source #

labelProxy (GenTx (ShelleyBlock proto era)) → Text Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

toCBORGenTx (ShelleyBlock proto era) → Encoding Source #

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

decCBORDecoder s (TxId (GenTx (ShelleyBlock proto era))) Source #

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

encCBORTxId (GenTx (ShelleyBlock proto era)) → Encoding Source #

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

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

Eq (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

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

Eq (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

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

Eq (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

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

Ord (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

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

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

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

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

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

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

NoThunks (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

NoThunks (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

NoThunks (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunksContextTxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) Source #

wNoThunksContextTxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) Source #

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

ConvertRawTxId (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

HasTxId (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

Condense (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 ⇒ 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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

data GenTx ByronBlock Source #

Generalized transactions in Byron

This is effectively the same as AMempoolPayload but we cache the transaction ID (a hash).

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

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.18.0.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

type Rep (Validated (GenTx ByronBlock)) = D1 ('MetaData "Validated" "Ouroboros.Consensus.Byron.Ledger.Mempool" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'True) (C1 ('MetaCons "ValidatedByronTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "forgetValidatedByronTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenTx ByronBlock))))
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-cardano-0.16.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)))))
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.18.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs))))
type Rep (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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-cardano-0.16.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.18.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
newtype Validated (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype Validated (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.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))
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

data TxId (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.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 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
SerialiseNodeToClient ByronBlock (GenTxId ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

SerialiseNodeToNode ByronBlock (GenTxId ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

ShowProxy (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Show (GenTxId ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTxId (ShelleyBlock proto era) → ShowS #

showGenTxId (ShelleyBlock proto era) → String #

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

decCBORDecoder s (TxId (GenTx (ShelleyBlock proto era))) Source #

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

encCBORTxId (GenTx (ShelleyBlock proto era)) → Encoding Source #

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

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

Eq (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

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

Ord (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

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

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

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

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

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

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

NoThunks (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunksContextTxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) Source #

wNoThunksContextTxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) Source #

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

Condense (GenTxId ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

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.18.0.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

data TxId (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.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 #

Generic (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Associated Types

type Rep (Validated (GenTx ByronBlock)) ∷ TypeType #

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 #

Methods

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

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

Show (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

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

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

Eq (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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 #

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

NoThunks (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

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.18.0.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

type Rep (Validated (GenTx ByronBlock)) = D1 ('MetaData "Validated" "Ouroboros.Consensus.Byron.Ledger.Mempool" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'True) (C1 ('MetaCons "ValidatedByronTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "forgetValidatedByronTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenTx ByronBlock))))
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-cardano-0.16.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

newtype Validated (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.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))

Transaction IDs

Serialisation

decodeByronGenTxDecoder s (GenTx ByronBlock) Source #

The ByteString annotation will be the canonical encoding.

While the new implementation does not care about canonical encodings, the old one does. When a generalised transaction arrives that is not in its canonical encoding (only the ATxAux of the ByronTx can be produced by nodes that are not under our control), the old implementation will reject it. Therefore, we need to reject them too. See #905.

We use the ledger to check for canonical encodings: the ledger will check whether the signed hash of the transaction (in the case of a ATxAux, the transaction witness) matches the annotated bytestring. Is therefore important that the annotated bytestring be the canonical encoding, not the original, possibly non-canonical encoding.

Low-level API (primarily for testing)

Auxiliary functions

countByronGenTxsByronBlockWord64 Source #

Count all (generalized) transactions in the block

Orphan instances

HasTxs ByronBlock Source # 
Instance details

LedgerSupportsMempool ByronBlock Source # 
Instance details

TxLimits ByronBlock Source # 
Instance details

Associated Types

type TxMeasure ByronBlock Source #

ShowProxy ApplyMempoolPayloadErr Source # 
Instance details

ShowProxy (GenTx ByronBlock) Source # 
Instance details

ShowProxy (TxId (GenTx ByronBlock)) Source # 
Instance details

Generic (Validated (GenTx ByronBlock)) Source # 
Instance details

Associated Types

type Rep (Validated (GenTx ByronBlock)) ∷ TypeType #

Generic (GenTx ByronBlock) Source # 
Instance details

Associated Types

type Rep (GenTx ByronBlock) ∷ TypeType #

Show (Validated (GenTx ByronBlock)) Source # 
Instance details

Show (GenTx ByronBlock) Source # 
Instance details

Show (GenTxId ByronBlock) Source # 
Instance details

Eq (Validated (GenTx ByronBlock)) Source # 
Instance details

Eq (GenTx ByronBlock) Source # 
Instance details

Eq (TxId (GenTx ByronBlock)) Source # 
Instance details

Ord (TxId (GenTx ByronBlock)) Source # 
Instance details

NoThunks (Validated (GenTx ByronBlock)) Source # 
Instance details

NoThunks (GenTx ByronBlock) Source # 
Instance details

NoThunks (TxId (GenTx ByronBlock)) Source # 
Instance details

ConvertRawTxId (GenTx ByronBlock) Source # 
Instance details

HasTxId (GenTx ByronBlock) Source # 
Instance details

Condense (GenTx ByronBlock) Source # 
Instance details

Condense (GenTxId ByronBlock) Source # 
Instance details