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

Ouroboros.Consensus.Shelley.Node

Synopsis

Documentation

newtype MaxMajorProtVer Source #

The maximum major protocol version.

Must be at least the current major protocol version. For Cardano mainnet, the Shelley era has major protocol verison 2.

Constructors

MaxMajorProtVer 

Fields

Instances

Instances details
Eq MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Show MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Generic MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Associated Types

type Rep MaxMajorProtVerTypeType Source #

NoThunks MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Methods

noThunks ∷ Context → MaxMajorProtVerIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → MaxMajorProtVerIO (Maybe ThunkInfo) #

showTypeOfProxy MaxMajorProtVerString #

type Rep MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

type Rep MaxMajorProtVer = D1 ('MetaData "MaxMajorProtVer" "Ouroboros.Consensus.Protocol.Praos.Common" "ouroboros-consensus-protocol-0.3.1.0-inplace" 'True) (C1 ('MetaCons "MaxMajorProtVer" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMaxMajorProtVer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))

data ProtocolParamsMary c Source #

Parameters needed to run Mary

data ProtocolParamsShelleyBased era Source #

Parameters common to all Shelley-based ledgers.

When running a chain with multiple Shelley-based eras, in addition to the per-era protocol parameters, one value of ProtocolParamsShelleyBased will be needed, which is shared among all Shelley-based eras.

The era parameter determines from which era the genesis config will be used.

Constructors

ProtocolParamsShelleyBased 

Fields

data Nonce #

Constructors

Nonce !(Hash Blake2b_256 Nonce) 
NeutralNonce 

Instances

Instances details
Eq Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

(==)NonceNonceBool Source #

(/=)NonceNonceBool Source #

Ord Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

compareNonceNonceOrdering Source #

(<)NonceNonceBool Source #

(<=)NonceNonceBool Source #

(>)NonceNonceBool Source #

(>=)NonceNonceBool Source #

maxNonceNonceNonce Source #

minNonceNonceNonce Source #

Show Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Generic Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep NonceTypeType Source #

Methods

fromNonceRep Nonce x Source #

toRep Nonce x → Nonce Source #

NFData Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

rnfNonce → () Source #

NoThunks Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

noThunks ∷ Context → NonceIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → NonceIO (Maybe ThunkInfo) #

showTypeOfProxy NonceString #

ToCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBORNonce → Encoding

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

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

DecCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBOR ∷ Decoder s Nonce

dropCBORProxy Nonce → Decoder s ()

labelProxy NonceText

EncCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

encCBORNonce → Encoding

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

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

FromCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR ∷ Decoder s Nonce

labelProxy NonceText

FromJSON Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON ∷ Value → Parser Nonce

parseJSONList ∷ Value → Parser [Nonce]

ToExpr Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toExprNonce → Expr

listToExpr ∷ [Nonce] → Expr

ToJSON Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSONNonce → Value

toEncodingNonce → Encoding

toJSONList ∷ [Nonce] → Value

toEncodingList ∷ [Nonce] → Encoding

type Rep Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

type Rep Nonce = D1 ('MetaData "Nonce" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.0.0.0-bd78daa4b267dd5077191bcdf8063ce0cc95e53fc5e214cefb9a40c991fa58a9" 'False) (C1 ('MetaCons "Nonce" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash Blake2b_256 Nonce))) :+: C1 ('MetaCons "NeutralNonce" 'PrefixI 'False) (U1TypeType))

data ProtVer #

Constructors

ProtVer 

Fields

Instances

Instances details
Eq ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

(==)ProtVerProtVerBool Source #

(/=)ProtVerProtVerBool Source #

Ord ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Show ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Generic ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep ProtVerTypeType Source #

Methods

fromProtVerRep ProtVer x Source #

toRep ProtVer x → ProtVer Source #

NFData ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

rnfProtVer → () Source #

NoThunks ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

noThunks ∷ Context → ProtVerIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ProtVerIO (Maybe ThunkInfo) #

showTypeOfProxy ProtVerString #

EncCBORGroup ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

encCBORGroupProtVer → Encoding

encodedGroupSizeExpr ∷ (∀ x. EncCBOR x ⇒ Proxy x → Size) → Proxy ProtVer → Size

listLenProtVerWord

listLenBoundProxy ProtVerWord

ToCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBORProtVer → Encoding

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

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

DecCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBOR ∷ Decoder s ProtVer

dropCBORProxy ProtVer → Decoder s ()

labelProxy ProtVerText

EncCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

encCBORProtVer → Encoding

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

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

DecCBORGroup ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBORGroup ∷ Decoder s ProtVer

FromCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR ∷ Decoder s ProtVer

labelProxy ProtVerText

FromJSON ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON ∷ Value → Parser ProtVer

parseJSONList ∷ Value → Parser [ProtVer]

ToExpr ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toExprProtVer → Expr

listToExpr ∷ [ProtVer] → Expr

ToJSON ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSONProtVer → Value

toEncodingProtVer → Encoding

toJSONList ∷ [ProtVer] → Value

toEncodingList ∷ [ProtVer] → Encoding

type Rep ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

type Rep ProtVer = D1 ('MetaData "ProtVer" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.0.0.0-bd78daa4b267dd5077191bcdf8063ce0cc95e53fc5e214cefb9a40c991fa58a9" 'False) (C1 ('MetaCons "ProtVer" 'PrefixI 'True) (S1 ('MetaSel ('Just "pvMajor") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Version) :*: S1 ('MetaSel ('Just "pvMinor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural)))

data ShelleyGenesis c #

Constructors

ShelleyGenesis 

Fields

Instances

Instances details
Crypto c ⇒ Eq (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Crypto c ⇒ Show (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Generic (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Associated Types

type Rep (ShelleyGenesis c) ∷ TypeType Source #

Crypto c ⇒ NoThunks (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

noThunks ∷ Context → ShelleyGenesis c → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ShelleyGenesis c → IO (Maybe ThunkInfo) #

showTypeOfProxy (ShelleyGenesis c) → String #

Crypto c ⇒ ToCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toCBORShelleyGenesis c → Encoding

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

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

Crypto c ⇒ DecCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

decCBOR ∷ Decoder s (ShelleyGenesis c)

dropCBORProxy (ShelleyGenesis c) → Decoder s ()

labelProxy (ShelleyGenesis c) → Text

Crypto c ⇒ EncCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

encCBORShelleyGenesis c → Encoding

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (ShelleyGenesis c) → Size

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [ShelleyGenesis c] → Size

Crypto c ⇒ FromCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

fromCBOR ∷ Decoder s (ShelleyGenesis c)

labelProxy (ShelleyGenesis c) → Text

Crypto c ⇒ FromJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

parseJSON ∷ Value → Parser (ShelleyGenesis c)

parseJSONList ∷ Value → Parser [ShelleyGenesis c]

Crypto c ⇒ ToJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toJSONShelleyGenesis c → Value

toEncodingShelleyGenesis c → Encoding

toJSONList ∷ [ShelleyGenesis c] → Value

toEncodingList ∷ [ShelleyGenesis c] → Encoding

type Rep (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

type Rep (ShelleyGenesis c) = D1 ('MetaData "ShelleyGenesis" "Cardano.Ledger.Shelley.Genesis" "cardano-ledger-shelley-1.0.0.0-90dea60a9745bbffa0ea5e6a6a70a7440ca213db291912c1f6465bb28913be6b" 'False) (C1 ('MetaCons "ShelleyGenesis" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sgSystemStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "sgNetworkMagic") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: S1 ('MetaSel ('Just "sgNetworkId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Network))) :*: ((S1 ('MetaSel ('Just "sgActiveSlotsCoeff") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PositiveUnitInterval) :*: S1 ('MetaSel ('Just "sgSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "sgEpochLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochSize) :*: S1 ('MetaSel ('Just "sgSlotsPerKESPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64)))) :*: (((S1 ('MetaSel ('Just "sgMaxKESEvolutions") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "sgSlotLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NominalDiffTimeMicro)) :*: (S1 ('MetaSel ('Just "sgUpdateQuorum") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "sgMaxLovelaceSupply") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "sgProtocolParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams (ShelleyEra c))) :*: S1 ('MetaSel ('Just "sgGenDelegs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'Genesis c) (GenDelegPair c)))) :*: (S1 ('MetaSel ('Just "sgInitialFunds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (Addr c) Coin)) :*: S1 ('MetaSel ('Just "sgStaking") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ShelleyGenesisStaking c)))))))

data ShelleyGenesisStaking c #

Constructors

ShelleyGenesisStaking 

Fields

  • sgsPools ∷ ListMap (KeyHash 'StakePool c) (PoolParams c)
     
  • sgsStake ∷ ListMap (KeyHash 'Staking c) (KeyHash 'StakePool c)
     

Instances

Instances details
Eq (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Show (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Generic (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Associated Types

type Rep (ShelleyGenesisStaking c) ∷ TypeType Source #

NoThunks (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

noThunks ∷ Context → ShelleyGenesisStaking c → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ShelleyGenesisStaking c → IO (Maybe ThunkInfo) #

showTypeOfProxy (ShelleyGenesisStaking c) → String #

Crypto c ⇒ DecCBOR (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

decCBOR ∷ Decoder s (ShelleyGenesisStaking c)

dropCBORProxy (ShelleyGenesisStaking c) → Decoder s ()

labelProxy (ShelleyGenesisStaking c) → Text

Crypto c ⇒ EncCBOR (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

encCBORShelleyGenesisStaking c → Encoding

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (ShelleyGenesisStaking c) → Size

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [ShelleyGenesisStaking c] → Size

Crypto c ⇒ FromJSON (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

parseJSON ∷ Value → Parser (ShelleyGenesisStaking c)

parseJSONList ∷ Value → Parser [ShelleyGenesisStaking c]

Crypto c ⇒ ToJSON (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toJSONShelleyGenesisStaking c → Value

toEncodingShelleyGenesisStaking c → Encoding

toJSONList ∷ [ShelleyGenesisStaking c] → Value

toEncodingList ∷ [ShelleyGenesisStaking c] → Encoding

type Rep (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

type Rep (ShelleyGenesisStaking c) = D1 ('MetaData "ShelleyGenesisStaking" "Cardano.Ledger.Shelley.Genesis" "cardano-ledger-shelley-1.0.0.0-90dea60a9745bbffa0ea5e6a6a70a7440ca213db291912c1f6465bb28913be6b" 'False) (C1 ('MetaCons "ShelleyGenesisStaking" 'PrefixI 'True) (S1 ('MetaSel ('Just "sgsPools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (KeyHash 'StakePool c) (PoolParams c))) :*: S1 ('MetaSel ('Just "sgsStake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (KeyHash 'Staking c) (KeyHash 'StakePool c)))))

data ShelleyLeaderCredentials c Source #

Constructors

ShelleyLeaderCredentials 

Fields

protocolInfoTPraosShelleyBased ∷ ∀ m era c. (IOLike m, PraosCrypto c, ShelleyCompatible (TPraos c) era, TxLimits (ShelleyBlock (TPraos c) era), c ~ EraCrypto era) ⇒ ProtocolParamsShelleyBased era → (AdditionalGenesisConfig era, TranslationContext era) → ProtVerTxOverrides (ShelleyBlock (TPraos c) era) → ProtocolInfo m (ShelleyBlock (TPraos c) era) Source #

registerGenesisStaking ∷ ∀ era. ShelleyBasedEra era ⇒ ShelleyGenesisStaking (EraCrypto era) → NewEpochState era → NewEpochState era Source #

Register the initial staking information in the NewEpochState.

HERE BE DRAGONS! This function is intended to help in testing.

In production, the genesis should not contain any initial staking.

Any existing staking information is overridden, but the UTxO is left untouched.

TODO adapt and reuse registerGenesisStaking from cardano-ledger.

registerInitialFunds ∷ ∀ era. (ShelleyBasedEra era, HasCallStack) ⇒ Map (Addr (EraCrypto era)) Coin → NewEpochState era → NewEpochState era Source #

Register the initial funds in the NewEpochState.

HERE BE DRAGONS! This function is intended to help in testing.

In production, the genesis should not contain any initial funds.

The given funds are added to the existing UTxO.

PRECONDITION: the given funds must not be part of the existing UTxO. > forall (addr, _) in initialFunds. > Map.notElem (SL.initialFundsPseudoTxIn addr) existingUTxO

PROPERTY: > genesisUTxO genesis > == genesisUTxO' (sgInitialFunds genesis) > == extractUTxO (registerInitialFunds (sgInitialFunds genesis) > NewEpochState)

TODO move to cardano-ledger-specs.

validateGenesisPraosCrypto c ⇒ ShelleyGenesis c → Either String () Source #

Check the validity of the genesis config. To be used in conjunction with assertWithMsg.

Orphan instances

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

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