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

Ouroboros.Consensus.Shelley.Protocol.Abstract

Description

Commonality between multiple protocols.

Everything in this module is indexed on the protocol (or the crypto), rather than on the block type. This allows it to be imported in Ouroboros.Consensus.Shelley.Ledger.Block.

Synopsis

Documentation

type family ProtoCrypto proto :: Type Source #

Instances

Instances details
type ProtoCrypto (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Praos

type ProtoCrypto (Praos c) = c
type ProtoCrypto (TPraos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.TPraos

type ProtoCrypto (TPraos c) = c

class (Eq (EnvelopeCheckError proto), NoThunks (EnvelopeCheckError proto), Show (EnvelopeCheckError proto)) => ProtocolHeaderSupportsEnvelope proto where Source #

Indicates that the header (determined by the protocol) supports " Envelope " functionality. Envelope functionality refers to the minimal functionality required to construct a chain.

Associated Types

type EnvelopeCheckError proto :: Type Source #

Methods

pHeaderHash :: ShelleyProtocolHeader proto -> ShelleyHash (ProtoCrypto proto) Source #

pHeaderPrevHash :: ShelleyProtocolHeader proto -> PrevHash (ProtoCrypto proto) Source #

pHeaderBodyHash :: ShelleyProtocolHeader proto -> Hash (ProtoCrypto proto) EraIndependentBlockBody Source #

pHeaderSlot :: ShelleyProtocolHeader proto -> SlotNo Source #

pHeaderBlock :: ShelleyProtocolHeader proto -> BlockNo Source #

pHeaderSize :: ShelleyProtocolHeader proto -> Natural Source #

pHeaderBlockSize :: ShelleyProtocolHeader proto -> Natural Source #

envelopeChecks :: ConsensusConfig proto -> LedgerView proto -> ShelleyProtocolHeader proto -> Except (EnvelopeCheckError proto) () Source #

Carry out any protocol-specific envelope checks. For example, this might check things like maximum header size.

Instances

Instances details
PraosCrypto c => ProtocolHeaderSupportsEnvelope (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Praos

Associated Types

type EnvelopeCheckError (Praos c) Source #

Methods

pHeaderHash :: ShelleyProtocolHeader (Praos c) -> ShelleyHash (ProtoCrypto (Praos c)) Source #

pHeaderPrevHash :: ShelleyProtocolHeader (Praos c) -> PrevHash (ProtoCrypto (Praos c)) Source #

pHeaderBodyHash :: ShelleyProtocolHeader (Praos c) -> Hash (ProtoCrypto (Praos c)) EraIndependentBlockBody Source #

pHeaderSlot :: ShelleyProtocolHeader (Praos c) -> SlotNo Source #

pHeaderBlock :: ShelleyProtocolHeader (Praos c) -> BlockNo Source #

pHeaderSize :: ShelleyProtocolHeader (Praos c) -> Natural Source #

pHeaderBlockSize :: ShelleyProtocolHeader (Praos c) -> Natural Source #

envelopeChecks :: ConsensusConfig (Praos c) -> LedgerView (Praos c) -> ShelleyProtocolHeader (Praos c) -> Except (EnvelopeCheckError (Praos c)) () Source #

PraosCrypto c => ProtocolHeaderSupportsEnvelope (TPraos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.TPraos

Associated Types

type EnvelopeCheckError (TPraos c) Source #

Methods

pHeaderHash :: ShelleyProtocolHeader (TPraos c) -> ShelleyHash (ProtoCrypto (TPraos c)) Source #

pHeaderPrevHash :: ShelleyProtocolHeader (TPraos c) -> PrevHash (ProtoCrypto (TPraos c)) Source #

pHeaderBodyHash :: ShelleyProtocolHeader (TPraos c) -> Hash (ProtoCrypto (TPraos c)) EraIndependentBlockBody Source #

pHeaderSlot :: ShelleyProtocolHeader (TPraos c) -> SlotNo Source #

pHeaderBlock :: ShelleyProtocolHeader (TPraos c) -> BlockNo Source #

pHeaderSize :: ShelleyProtocolHeader (TPraos c) -> Natural Source #

pHeaderBlockSize :: ShelleyProtocolHeader (TPraos c) -> Natural Source #

envelopeChecks :: ConsensusConfig (TPraos c) -> LedgerView (TPraos c) -> ShelleyProtocolHeader (TPraos c) -> Except (EnvelopeCheckError (TPraos c)) () Source #

class ProtocolHeaderSupportsKES proto where Source #

ProtocolHeaderSupportsKES describes functionality common to protocols using key evolving signature schemes. This includes verifying the header integrity (e.g. validating the KES signature), as well as constructing the header (made specific to KES-using protocols through the need to handle the hot key).

Methods

configSlotsPerKESPeriod :: ConsensusConfig proto -> Word64 Source #

Extract the "slots per KES period" value from the protocol config.

Note that we do not require ConsensusConfig in verifyHeaderIntegrity since that function is also invoked with StorageConfig.

verifyHeaderIntegrity Source #

Arguments

:: Word64

Slots per KES period

-> ShelleyProtocolHeader proto 
-> Bool 

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

mkHeader Source #

Arguments

:: forall crypto m. (Crypto crypto, Monad m, crypto ~ ProtoCrypto proto) 
=> HotKey crypto m 
-> CanBeLeader proto 
-> IsLeader proto 
-> SlotNo

Slot no

-> BlockNo

Block no

-> PrevHash crypto

Hash of the previous block

-> Hash crypto EraIndependentBlockBody

Hash of the block body to include in the header

-> Int

Size of the block body

-> ProtVer

Protocol version

-> m (ShelleyProtocolHeader proto) 

Instances

Instances details
PraosCrypto c => ProtocolHeaderSupportsKES (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Praos

Methods

configSlotsPerKESPeriod :: ConsensusConfig (Praos c) -> Word64 Source #

verifyHeaderIntegrity :: Word64 -> ShelleyProtocolHeader (Praos c) -> Bool Source #

mkHeader :: (Crypto crypto, Monad m, crypto ~ ProtoCrypto (Praos c)) => HotKey crypto m -> CanBeLeader (Praos c) -> IsLeader (Praos c) -> SlotNo -> BlockNo -> PrevHash crypto -> Hash crypto EraIndependentBlockBody -> Int -> ProtVer -> m (ShelleyProtocolHeader (Praos c)) Source #

PraosCrypto c => ProtocolHeaderSupportsKES (TPraos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.TPraos

Methods

configSlotsPerKESPeriod :: ConsensusConfig (TPraos c) -> Word64 Source #

verifyHeaderIntegrity :: Word64 -> ShelleyProtocolHeader (TPraos c) -> Bool Source #

mkHeader :: (Crypto crypto, Monad m, crypto ~ ProtoCrypto (TPraos c)) => HotKey crypto m -> CanBeLeader (TPraos c) -> IsLeader (TPraos c) -> SlotNo -> BlockNo -> PrevHash crypto -> Hash crypto EraIndependentBlockBody -> Int -> ProtVer -> m (ShelleyProtocolHeader (TPraos c)) Source #

class ProtocolHeaderSupportsLedger proto where Source #

Indicates that the protocol header supports the Shelley ledger. We may need to generalise this if, in the future, the ledger requires different things from the protocol.

Methods

mkHeaderView :: ShelleyProtocolHeader proto -> BHeaderView (ProtoCrypto proto) Source #

Instances

Instances details
PraosCrypto c => ProtocolHeaderSupportsLedger (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Praos

Methods

mkHeaderView :: ShelleyProtocolHeader (Praos c) -> BHeaderView (ProtoCrypto (Praos c)) Source #

PraosCrypto c => ProtocolHeaderSupportsLedger (TPraos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.TPraos

Methods

mkHeaderView :: ShelleyProtocolHeader (TPraos c) -> BHeaderView (ProtoCrypto (TPraos c)) Source #

class ProtocolHeaderSupportsProtocol proto where Source #

ProtocolHeaderSupportsProtocol` provides support for the concrete block header to support the ConsensusProtocol itself.

Associated Types

type CannotForgeError proto :: Type Source #

Methods

protocolHeaderView :: ShelleyProtocolHeader proto -> ValidateView proto Source #

pHeaderIssuer :: ShelleyProtocolHeader proto -> VKey 'BlockIssuer (ProtoCrypto proto) Source #

pHeaderIssueNo :: ShelleyProtocolHeader proto -> Word64 Source #

pTieBreakVRFValue :: ShelleyProtocolHeader proto -> OutputVRF (VRF (ProtoCrypto proto)) Source #

A VRF value in the header, used to choose between otherwise equally preferable chains.

Instances

Instances details
PraosCrypto c => ProtocolHeaderSupportsProtocol (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Praos

Associated Types

type CannotForgeError (Praos c) Source #

Methods

protocolHeaderView :: ShelleyProtocolHeader (Praos c) -> ValidateView (Praos c) Source #

pHeaderIssuer :: ShelleyProtocolHeader (Praos c) -> VKey 'BlockIssuer (ProtoCrypto (Praos c)) Source #

pHeaderIssueNo :: ShelleyProtocolHeader (Praos c) -> Word64 Source #

pTieBreakVRFValue :: ShelleyProtocolHeader (Praos c) -> OutputVRF (VRF (ProtoCrypto (Praos c))) Source #

PraosCrypto c => ProtocolHeaderSupportsProtocol (TPraos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.TPraos

Associated Types

type CannotForgeError (TPraos c) Source #

Methods

protocolHeaderView :: ShelleyProtocolHeader (TPraos c) -> ValidateView (TPraos c) Source #

pHeaderIssuer :: ShelleyProtocolHeader (TPraos c) -> VKey 'BlockIssuer (ProtoCrypto (TPraos c)) Source #

pHeaderIssueNo :: ShelleyProtocolHeader (TPraos c) -> Word64 Source #

pTieBreakVRFValue :: ShelleyProtocolHeader (TPraos c) -> OutputVRF (VRF (ProtoCrypto (TPraos c))) Source #

newtype ShelleyHash crypto Source #

Constructors

ShelleyHash 

Fields

Instances

Instances details
Generic (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Associated Types

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

Methods

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

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

Show (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

showsPrec :: Int -> ShelleyHash crypto -> ShowS Source #

show :: ShelleyHash crypto -> String Source #

showList :: [ShelleyHash crypto] -> ShowS Source #

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

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

fromCBOR :: Decoder s (ShelleyHash crypto)

label :: Proxy (ShelleyHash crypto) -> Text

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

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

toCBOR :: ShelleyHash crypto -> Encoding

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

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

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

compare :: ShelleyHash 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 #

max :: ShelleyHash crypto -> ShelleyHash crypto -> ShelleyHash crypto Source #

min :: ShelleyHash crypto -> ShelleyHash crypto -> ShelleyHash crypto 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)

showTypeOf :: Proxy (ShelleyHash crypto) -> String

Condense (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

condense :: ShelleyHash crypto -> String

Crypto crypto => Serialise (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

encode :: ShelleyHash crypto -> Encoding

decode :: Decoder s (ShelleyHash crypto)

encodeList :: [ShelleyHash crypto] -> Encoding

decodeList :: Decoder s [ShelleyHash crypto]

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-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "ShelleyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unShelleyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash crypto EraIndependentBlockHeader))))

class (ConsensusProtocol proto, Typeable (ShelleyProtocolHeader proto), ProtocolHeaderSupportsEnvelope proto, ProtocolHeaderSupportsKES proto, ProtocolHeaderSupportsProtocol proto, ProtocolHeaderSupportsLedger proto, Serialise (ChainDepState proto), SignedHeader (ShelleyProtocolHeader proto)) => ShelleyProtocol proto Source #

Instances

Instances details
PraosCrypto c => ShelleyProtocol (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Praos

PraosCrypto c => ShelleyProtocol (TPraos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.TPraos

type family ShelleyProtocolHeader proto = (sh :: Type) | sh -> proto Source #

Shelley header, determined by the associated protocol.

Instances

Instances details
type ShelleyProtocolHeader (Praos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Praos

type ShelleyProtocolHeader (Praos c) = Header c
type ShelleyProtocolHeader (TPraos c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.TPraos

type ShelleyProtocolHeader (TPraos c) = BHeader c