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

Ouroboros.Consensus.Shelley.Node

Synopsis

Documentation

newtype MaxMajorProtVer #

Constructors

MaxMajorProtVer 

Fields

Instances

Instances details
Generic MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Associated Types

type Rep MaxMajorProtVer :: Type -> Type Source #

Show MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Eq MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

NoThunks MaxMajorProtVer 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Common

Methods

noThunks :: Context -> MaxMajorProtVer -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> MaxMajorProtVer -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy MaxMajorProtVer -> String

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.6.0.0-9L9Rwb3KvaS6sYVJ3OHbE2" 'True) (C1 ('MetaCons "MaxMajorProtVer" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMaxMajorProtVer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)))

data family ProtocolParams blk #

Instances

Instances details
data ProtocolParams ByronBlock Source #

Parameters needed to run Byron

Instance details

Defined in Ouroboros.Consensus.Byron.Node

data ProtocolParams (CardanoBlock c) Source #

Parameters needed to run Cardano.

Instance details

Defined in Ouroboros.Consensus.Cardano.Node

data ProtocolParams (ShelleyBlock (Praos c) (BabbageEra c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Praos

data ProtocolParams (ShelleyBlock (Praos c) (ConwayEra c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Praos

data ProtocolParams (ShelleyBlock (TPraos c) (AllegraEra c)) Source #

Parameters needed to run Allegra

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParams (ShelleyBlock (TPraos c) (AlonzoEra c)) Source #

Parameters needed to run Alonzo

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParams (ShelleyBlock (TPraos c) (MaryEra c)) Source #

Parameters needed to run Mary

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParams (ShelleyBlock (TPraos c) (ShelleyEra c)) Source #

Parameters needed to run Shelley

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParamsShelleyBased c 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.

Constructors

ProtocolParamsShelleyBased 

Fields

data Nonce #

Constructors

Nonce !(Hash Blake2b_256 Nonce) 
NeutralNonce 

Instances

Instances details
FromJSON Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser Nonce

parseJSONList :: Value -> Parser [Nonce]

omittedField :: Maybe Nonce

ToJSON Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Nonce -> Value

toEncoding :: Nonce -> Encoding

toJSONList :: [Nonce] -> Value

toEncodingList :: [Nonce] -> Encoding

omitField :: Nonce -> Bool

Generic Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep Nonce :: Type -> Type Source #

Methods

from :: Nonce -> Rep Nonce x Source #

to :: Rep Nonce x -> Nonce Source #

Show Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR :: Decoder s Nonce

label :: Proxy Nonce -> Text

ToCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: Nonce -> Encoding

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

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

DecCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBOR :: Decoder s Nonce

dropCBOR :: Proxy Nonce -> Decoder s ()

label :: Proxy Nonce -> Text

EncCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

encCBOR :: Nonce -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Nonce -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Nonce] -> Size

NFData Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

rnf :: Nonce -> () Source #

Eq Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

(==) :: Nonce -> Nonce -> Bool Source #

(/=) :: Nonce -> Nonce -> Bool Source #

Ord Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

NoThunks Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

noThunks :: Context -> Nonce -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Nonce -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy Nonce -> String

ToExpr Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toExpr :: Nonce -> Expr

listToExpr :: [Nonce] -> Expr

type Rep Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

type Rep Nonce = D1 ('MetaData "Nonce" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.9.0.0-1PU7Gr2wD6e8bMdYoXBOob" 'False) (C1 ('MetaCons "Nonce" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash Blake2b_256 Nonce))) :+: C1 ('MetaCons "NeutralNonce" 'PrefixI 'False) (U1 :: Type -> Type))

data ProtVer #

Constructors

ProtVer 

Fields

Instances

Instances details
FromJSON ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser ProtVer

parseJSONList :: Value -> Parser [ProtVer]

omittedField :: Maybe ProtVer

ToJSON ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: ProtVer -> Value

toEncoding :: ProtVer -> Encoding

toJSONList :: [ProtVer] -> Value

toEncodingList :: [ProtVer] -> Encoding

omitField :: ProtVer -> Bool

Generic ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep ProtVer :: Type -> Type Source #

Show ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

FromCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR :: Decoder s ProtVer

label :: Proxy ProtVer -> Text

ToCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: ProtVer -> Encoding

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

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

DecCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBOR :: Decoder s ProtVer

dropCBOR :: Proxy ProtVer -> Decoder s ()

label :: Proxy ProtVer -> Text

EncCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

encCBOR :: ProtVer -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ProtVer -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ProtVer] -> Size

DecCBORGroup ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBORGroup :: Decoder s ProtVer

EncCBORGroup ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

encCBORGroup :: ProtVer -> Encoding

encodedGroupSizeExpr :: (forall x. EncCBOR x => Proxy x -> Size) -> Proxy ProtVer -> Size

listLen :: ProtVer -> Word

listLenBound :: Proxy ProtVer -> Word

NFData ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

rnf :: ProtVer -> () Source #

Eq ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Ord ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

NoThunks ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

noThunks :: Context -> ProtVer -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ProtVer -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy ProtVer -> String

ToExpr ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toExpr :: ProtVer -> Expr

listToExpr :: [ProtVer] -> Expr

type Rep ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

type Rep ProtVer = D1 ('MetaData "ProtVer" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.9.0.0-1PU7Gr2wD6e8bMdYoXBOob" '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 => FromJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

parseJSON :: Value -> Parser (ShelleyGenesis c)

parseJSONList :: Value -> Parser [ShelleyGenesis c]

omittedField :: Maybe (ShelleyGenesis c)

Crypto c => ToJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toJSON :: ShelleyGenesis c -> Value

toEncoding :: ShelleyGenesis c -> Encoding

toJSONList :: [ShelleyGenesis c] -> Value

toEncodingList :: [ShelleyGenesis c] -> Encoding

omitField :: ShelleyGenesis c -> Bool

Generic (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Associated Types

type Rep (ShelleyGenesis c) :: Type -> Type Source #

Crypto c => Show (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Crypto c => FromCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

fromCBOR :: Decoder s (ShelleyGenesis c)

label :: Proxy (ShelleyGenesis c) -> Text

Crypto c => ToCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toCBOR :: ShelleyGenesis c -> Encoding

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

encodedListSizeExpr :: (forall 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)

dropCBOR :: Proxy (ShelleyGenesis c) -> Decoder s ()

label :: Proxy (ShelleyGenesis c) -> Text

Crypto c => EncCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

encCBOR :: ShelleyGenesis c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyGenesis c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyGenesis c] -> Size

Crypto c => Eq (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

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)

showTypeOf :: Proxy (ShelleyGenesis c) -> String

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.8.0.0-163LAE5QwnDC1PvCpY1ebT" '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
Crypto c => FromJSON (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Crypto c => ToJSON (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Monoid (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Semigroup (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) :: Type -> Type Source #

Show (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Crypto c => DecCBOR (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

decCBOR :: Decoder s (ShelleyGenesisStaking c)

dropCBOR :: Proxy (ShelleyGenesisStaking c) -> Decoder s ()

label :: Proxy (ShelleyGenesisStaking c) -> Text

Crypto c => EncCBOR (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

encCBOR :: ShelleyGenesisStaking c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyGenesisStaking c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyGenesisStaking c] -> Size

Eq (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

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)

showTypeOf :: Proxy (ShelleyGenesisStaking c) -> String

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.8.0.0-163LAE5QwnDC1PvCpY1ebT" '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

protocolClientInfoShelley :: ProtocolClientInfo (ShelleyBlock proto era) Source #

protocolInfoShelley :: forall m c. (IOLike m, PraosCrypto c, ShelleyCompatible (TPraos c) (ShelleyEra c), TxLimits (ShelleyBlock (TPraos c) (ShelleyEra c))) => ShelleyGenesis c -> ProtocolParamsShelleyBased c -> ProtocolParams (ShelleyBlock (TPraos c) (ShelleyEra c)) -> (ProtocolInfo (ShelleyBlock (TPraos c) (ShelleyEra c)), m [BlockForging m (ShelleyBlock (TPraos c) (ShelleyEra c))]) Source #

protocolInfoTPraosShelleyBased :: forall m era c. (IOLike m, PraosCrypto c, ShelleyCompatible (TPraos c) era, TxLimits (ShelleyBlock (TPraos c) era), c ~ EraCrypto era) => ProtocolParamsShelleyBased c -> TransitionConfig era -> ProtVer -> TxOverrides (ShelleyBlock (TPraos c) era) -> (ProtocolInfo (ShelleyBlock (TPraos c) era), m [BlockForging m (ShelleyBlock (TPraos c) era)]) Source #

validateGenesis :: PraosCrypto 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 => BlockSupportsMetrics (ShelleyBlock proto era) Source # 
Instance details

Methods

isSelfIssued :: BlockConfig (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> WhetherSelfIssued

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