Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data BlockValidationMode
- toTxValidationMode :: BlockValidationMode -> TxValidationMode
- adoptedProtocolParameters :: State -> ProtocolParameters
- updateBody :: ( MonadError ChainValidationError m, MonadReader ValidationMode m) => BodyEnvironment -> BodyState -> ABlock ByteString -> m BodyState
- updateChainBlockOrBoundary :: ( MonadError ChainValidationError m, MonadReader ValidationMode m) => Config -> ChainValidationState -> ABlockOrBoundary ByteString -> m ChainValidationState
- updateChainBoundary :: MonadError ChainValidationError m => ChainValidationState -> ABoundaryBlock ByteString -> m ChainValidationState
- epochTransition :: EpochEnvironment -> State -> SlotNumber -> State
- headerIsValid :: ( MonadError ChainValidationError m, MonadReader ValidationMode m) => State -> AHeader ByteString -> m ()
- validateHeaderMatchesBody :: MonadError ProofValidationError m => AHeader ByteString -> ABody ByteString -> m ()
- updateBlock :: ( MonadError ChainValidationError m, MonadReader ValidationMode m) => Config -> ChainValidationState -> ABlock ByteString -> m ChainValidationState
-
data
BodyState
=
BodyState
{
- utxo :: ! UTxO
- updateState :: ! State
- delegationState :: ! State
-
data
BodyEnvironment
=
BodyEnvironment
{
- protocolMagic :: !( AProtocolMagic ByteString )
- utxoConfiguration :: ! UTxOConfiguration
- k :: ! BlockCount
- allowedDelegators :: !( Set KeyHash )
- protocolParameters :: ! ProtocolParameters
- currentEpoch :: ! EpochNumber
-
data
EpochEnvironment
=
EpochEnvironment
{
- protocolMagic :: !( Annotated ProtocolMagicId ByteString )
- k :: ! BlockCount
- allowedDelegators :: !( Set KeyHash )
- delegationMap :: ! Map
- currentEpoch :: ! EpochNumber
-
data
ChainValidationState
=
ChainValidationState
{
- cvsLastSlot :: ! SlotNumber
- cvsPreviousHash :: !( Either GenesisHash HeaderHash )
- cvsUtxo :: ! UTxO
- cvsUpdateState :: ! State
- cvsDelegationState :: ! State
- initialChainValidationState :: MonadError Error m => Config -> m ChainValidationState
-
data
ChainValidationError
- = ChainValidationBoundaryTooLarge
- | ChainValidationBlockAttributesTooLarge
- | ChainValidationBlockTooLarge Natural Natural
- | ChainValidationHeaderAttributesTooLarge
- | ChainValidationHeaderTooLarge Natural Natural
- | ChainValidationDelegationPayloadError Text
- | ChainValidationInvalidDelegation VerificationKey VerificationKey
- | ChainValidationGenesisHashMismatch GenesisHash GenesisHash
- | ChainValidationExpectedGenesisHash GenesisHash HeaderHash
- | ChainValidationExpectedHeaderHash HeaderHash GenesisHash
- | ChainValidationInvalidHash HeaderHash HeaderHash
- | ChainValidationMissingHash HeaderHash
- | ChainValidationUnexpectedGenesisHash HeaderHash
- | ChainValidationInvalidSignature BlockSignature
- | ChainValidationDelegationSchedulingError Error
- | ChainValidationProtocolMagicMismatch ProtocolMagicId ProtocolMagicId
- | ChainValidationSignatureLight
- | ChainValidationTooManyDelegations VerificationKey
- | ChainValidationUpdateError SlotNumber Error
- | ChainValidationUTxOValidationError UTxOValidationError
- | ChainValidationProofValidationError ProofValidationError
-
newtype
HeapSize
a =
HeapSize
{
- unHeapSize :: Int
-
newtype
UTxOSize
=
UTxOSize
{
- unUTxOSize :: Int
- calcUTxOSize :: UTxO -> ( HeapSize UTxO , UTxOSize )
- foldUTxO :: Environment -> UTxO -> Stream ( Of ( ABlock ByteString )) ( ExceptT ParseError ResIO ) () -> ExceptT Error ( ReaderT ValidationMode ResIO ) UTxO
- foldUTxOBlock :: Environment -> UTxO -> ABlock ByteString -> ExceptT Error ( ReaderT ValidationMode ResIO ) UTxO
-
data
Proof
=
Proof
{
- proofUTxO :: ! TxProof
- proofSsc :: ! SscProof
- proofDelegation :: !( Hash Payload )
- proofUpdate :: ! Proof
- data ProofValidationError
- mkProof :: Body -> Proof
- recoverProof :: ABody ByteString -> Proof
- type Header = AHeader ()
-
data
AHeader
a =
AHeader
{
- aHeaderProtocolMagicId :: !( Annotated ProtocolMagicId a)
- aHeaderPrevHash :: !( Annotated HeaderHash a)
- aHeaderSlot :: !( Annotated SlotNumber a)
- aHeaderDifficulty :: !( Annotated ChainDifficulty a)
- headerProtocolVersion :: ! ProtocolVersion
- headerSoftwareVersion :: ! SoftwareVersion
- aHeaderProof :: !( Annotated Proof a)
- headerGenesisKey :: ! VerificationKey
- headerSignature :: !( ABlockSignature a)
- headerAnnotation :: !a
- headerExtraAnnotation :: !a
- mkHeader :: ProtocolMagicId -> Either GenesisHash Header -> EpochSlots -> SlotNumber -> SigningKey -> Certificate -> Body -> ProtocolVersion -> SoftwareVersion -> Header
- mkHeaderExplicit :: ProtocolMagicId -> HeaderHash -> ChainDifficulty -> EpochSlots -> SlotNumber -> SigningKey -> Certificate -> Body -> ProtocolVersion -> SoftwareVersion -> Header
- headerProtocolMagicId :: AHeader a -> ProtocolMagicId
- headerPrevHash :: AHeader a -> HeaderHash
- headerProof :: AHeader a -> Proof
- headerSlot :: AHeader a -> SlotNumber
- headerIssuer :: AHeader a -> VerificationKey
- headerLength :: AHeader ByteString -> Natural
- headerDifficulty :: AHeader a -> ChainDifficulty
- headerToSign :: EpochSlots -> AHeader a -> ToSign
- toCBORHeader :: EpochSlots -> Header -> Encoding
- toCBORHeaderSize :: Proxy EpochSlots -> Proxy ( AHeader a) -> Size
- toCBORHeaderToHash :: EpochSlots -> Header -> Encoding
- fromCBORAHeader :: EpochSlots -> Decoder s ( AHeader ByteSpan )
- fromCBORHeader :: EpochSlots -> Decoder s Header
- fromCBORHeaderToHash :: EpochSlots -> Decoder s ( Maybe Header )
- wrapHeaderBytes :: ByteString -> ByteString
- toCBORBlockVersions :: ProtocolVersion -> SoftwareVersion -> Encoding
- toCBORBlockVersionsSize :: Proxy ProtocolVersion -> Proxy SoftwareVersion -> Size
- renderHeader :: EpochSlots -> Header -> Builder
-
data
ABoundaryHeader
a =
UnsafeABoundaryHeader
{
- boundaryPrevHash :: !( Either GenesisHash HeaderHash )
- boundaryEpoch :: ! Word64
- boundaryDifficulty :: ! ChainDifficulty
- boundaryHeaderAnnotation :: !a
- mkABoundaryHeader :: Either GenesisHash HeaderHash -> Word64 -> ChainDifficulty -> a -> ABoundaryHeader a
- toCBORABoundaryHeader :: ProtocolMagicId -> ABoundaryHeader a -> Encoding
- toCBORABoundaryHeaderSize :: Proxy ProtocolMagicId -> Proxy ( ABoundaryHeader a) -> Size
- fromCBORABoundaryHeader :: Decoder s ( ABoundaryHeader ByteSpan )
- boundaryHeaderHashAnnotated :: ABoundaryHeader ByteString -> HeaderHash
- wrapBoundaryBytes :: ByteString -> ByteString
- type HeaderHash = Hash Header
- headerHashF :: Format r ( HeaderHash -> r)
- hashHeader :: EpochSlots -> Header -> HeaderHash
- headerHashAnnotated :: AHeader ByteString -> HeaderHash
- genesisHeaderHash :: GenesisHash -> HeaderHash
- type BlockSignature = ABlockSignature ()
-
data
ABlockSignature
a =
ABlockSignature
{
- delegationCertificate :: !( ACertificate a)
- signature :: !( Signature ToSign )
-
data
ToSign
=
ToSign
{
- tsHeaderHash :: ! HeaderHash
- tsBodyProof :: ! Proof
- tsSlot :: ! EpochAndSlotCount
- tsDifficulty :: ! ChainDifficulty
- tsProtocolVersion :: ! ProtocolVersion
- tsSoftwareVersion :: ! SoftwareVersion
- recoverSignedBytes :: EpochSlots -> AHeader ByteString -> Annotated ToSign ByteString
- fromCBORBoundaryConsensusData :: Decoder s ( Word64 , ChainDifficulty )
- dropBoundaryExtraHeaderData :: Dropper s
- dropBoundaryExtraHeaderDataRetainGenesisTag :: Decoder s Bool
- dropBoundaryBody :: Dropper s
- dropBoundaryExtraBodyData :: Dropper s
- type Body = ABody ()
- pattern Body :: TxPayload -> SscPayload -> Payload -> Payload -> Body
-
data
ABody
a =
ABody
{
- bodyTxPayload :: !( ATxPayload a)
- bodySscPayload :: ! SscPayload
- bodyDlgPayload :: !( APayload a)
- bodyUpdatePayload :: !( APayload a)
- bodyTxs :: Body -> [ Tx ]
- bodyWitnesses :: Body -> [ TxWitness ]
- type Block = ABlock ()
-
data
ABlock
a =
ABlock
{
- blockHeader :: AHeader a
- blockBody :: ABody a
- blockAnnotation :: a
- mkBlock :: ProtocolMagicId -> ProtocolVersion -> SoftwareVersion -> Either GenesisHash Header -> EpochSlots -> SlotNumber -> SigningKey -> Certificate -> Body -> Block
- mkBlockExplicit :: ProtocolMagicId -> ProtocolVersion -> SoftwareVersion -> HeaderHash -> ChainDifficulty -> EpochSlots -> SlotNumber -> SigningKey -> Certificate -> Body -> Block
- blockHash :: EpochSlots -> Block -> HeaderHash
- blockHashAnnotated :: ABlock ByteString -> HeaderHash
- blockAProtocolMagicId :: ABlock a -> Annotated ProtocolMagicId a
- blockProtocolMagicId :: ABlock a -> ProtocolMagicId
- blockPrevHash :: ABlock a -> HeaderHash
- blockProof :: ABlock a -> Proof
- blockSlot :: ABlock a -> SlotNumber
- blockGenesisKey :: ABlock a -> VerificationKey
- blockIssuer :: ABlock a -> VerificationKey
- blockDifficulty :: ABlock a -> ChainDifficulty
- blockToSign :: EpochSlots -> ABlock a -> ToSign
- blockSignature :: ABlock a -> ABlockSignature a
- blockProtocolVersion :: ABlock a -> ProtocolVersion
- blockSoftwareVersion :: ABlock a -> SoftwareVersion
- blockTxPayload :: ABlock a -> ATxPayload a
- blockSscPayload :: ABlock a -> SscPayload
- blockDlgPayload :: ABlock a -> APayload a
- blockUpdatePayload :: ABlock a -> APayload a
- blockLength :: ABlock ByteString -> Natural
- toCBORBlock :: EpochSlots -> Block -> Encoding
- fromCBORABlock :: EpochSlots -> Decoder s ( ABlock ByteSpan )
- renderBlock :: EpochSlots -> Block -> Builder
-
data
ABlockOrBoundary
a
- = ABOBBlock ( ABlock a)
- | ABOBBoundary ( ABoundaryBlock a)
- toCBORABOBBlock :: EpochSlots -> ABlock a -> Encoding
- fromCBORABOBBlock :: EpochSlots -> Decoder s ( Maybe Block )
- fromCBORABlockOrBoundary :: EpochSlots -> Decoder s ( ABlockOrBoundary ByteSpan )
- toCBORABlockOrBoundary :: ProtocolMagicId -> EpochSlots -> ABlockOrBoundary a -> Encoding
-
data
ABoundaryBlock
a =
ABoundaryBlock
{
- boundaryBlockLength :: ! Int64
- boundaryHeader :: !( ABoundaryHeader a)
- boundaryBody :: !( ABoundaryBody a)
- boundaryAnnotation :: !a
- boundaryHashAnnotated :: ABoundaryBlock ByteString -> HeaderHash
- fromCBORABoundaryBlock :: Decoder s ( ABoundaryBlock ByteSpan )
- toCBORABoundaryBlock :: ProtocolMagicId -> ABoundaryBlock a -> Encoding
- toCBORABOBBoundary :: ProtocolMagicId -> ABoundaryBlock a -> Encoding
- boundaryBlockSlot :: EpochSlots -> Word64 -> SlotNumber
-
data
ABoundaryBody
a =
ABoundaryBody
{
- boundaryBodyAnnotation :: !a
-
data
ABlockOrBoundaryHdr
a
- = ABOBBlockHdr !( AHeader a)
- | ABOBBoundaryHdr !( ABoundaryHeader a)
- aBlockOrBoundaryHdr :: ( AHeader a -> b) -> ( ABoundaryHeader a -> b) -> ABlockOrBoundaryHdr a -> b
- fromCBORABlockOrBoundaryHdr :: EpochSlots -> Decoder s ( ABlockOrBoundaryHdr ByteSpan )
- toCBORABlockOrBoundaryHdr :: ABlockOrBoundaryHdr ByteString -> Encoding
- toCBORABlockOrBoundaryHdrSize :: Proxy ( ABlockOrBoundaryHdr a) -> Size
- abobHdrFromBlock :: ABlockOrBoundary a -> ABlockOrBoundaryHdr a
- abobHdrSlotNo :: EpochSlots -> ABlockOrBoundaryHdr a -> SlotNumber
- abobHdrChainDifficulty :: ABlockOrBoundaryHdr a -> ChainDifficulty
- abobHdrHash :: ABlockOrBoundaryHdr ByteString -> HeaderHash
- abobHdrPrevHash :: ABlockOrBoundaryHdr a -> Maybe HeaderHash
Documentation
data BlockValidationMode Source #
Indicates what sort of block validation should be performed.
BlockValidation |
Perform all block validations. |
NoBlockValidation |
Perform no block validations. |
Instances
Eq BlockValidationMode Source # | |
Defined in Cardano.Chain.Block.ValidationMode (==) :: BlockValidationMode -> BlockValidationMode -> Bool Source # (/=) :: BlockValidationMode -> BlockValidationMode -> Bool Source # |
|
Show BlockValidationMode Source # | |
Defined in Cardano.Chain.Block.ValidationMode |
toTxValidationMode :: BlockValidationMode -> TxValidationMode Source #
Translate a
BlockValidationMode
to an appropriate
TxValidationMode
.
adoptedProtocolParameters :: State -> ProtocolParameters Source #
Adopted protocol parameters
updateBody :: ( MonadError ChainValidationError m, MonadReader ValidationMode m) => BodyEnvironment -> BodyState -> ABlock ByteString -> m BodyState Source #
This is an implementation of the BBODY rule as per the chain specification.
Compared to
updateChain
, this does not validate any header level checks,
nor does it carry out anything which might be considered part of the
protocol.
updateChainBlockOrBoundary :: ( MonadError ChainValidationError m, MonadReader ValidationMode m) => Config -> ChainValidationState -> ABlockOrBoundary ByteString -> m ChainValidationState Source #
updateChainBoundary :: MonadError ChainValidationError m => ChainValidationState -> ABoundaryBlock ByteString -> m ChainValidationState Source #
epochTransition :: EpochEnvironment -> State -> SlotNumber -> State Source #
Perform epoch transition if we have moved across the epoch boundary
We pass through to the update interface UPIEC rule, which adopts any confirmed proposals and cleans up the state. This corresponds to the EPOCH rules from the Byron chain specification.
headerIsValid :: ( MonadError ChainValidationError m, MonadReader ValidationMode m) => State -> AHeader ByteString -> m () Source #
This is an implementation of the headerIsValid function from the Byron chain specification
validateHeaderMatchesBody :: MonadError ProofValidationError m => AHeader ByteString -> ABody ByteString -> m () Source #
updateBlock :: ( MonadError ChainValidationError m, MonadReader ValidationMode m) => Config -> ChainValidationState -> ABlock ByteString -> m ChainValidationState Source #
This represents the CHAIN rule. It is intended more for use in tests than in a real implementation, which will want to invoke its constituent rules directly.
Note that this also updates the previous block hash, which would usually be done as part of the PBFT rule.
BodyState | |
|
data BodyEnvironment Source #
BodyEnvironment | |
|
data EpochEnvironment Source #
EpochEnvironment | |
|
data ChainValidationState Source #
ChainValidationState | |
|
Instances
initialChainValidationState :: MonadError Error m => Config -> m ChainValidationState Source #
Create the state needed to validate the zeroth epoch of the chain. The zeroth epoch starts with a boundary block where the previous hash is the genesis hash.
data ChainValidationError Source #
ChainValidationBoundaryTooLarge |
The size of an epoch boundary block exceeds the limit |
ChainValidationBlockAttributesTooLarge |
The size of a block's attributes is non-zero |
ChainValidationBlockTooLarge Natural Natural |
The size of a regular block exceeds the limit |
ChainValidationHeaderAttributesTooLarge |
The size of a block header's attributes is non-zero |
ChainValidationHeaderTooLarge Natural Natural |
The size of a block header exceeds the limit |
ChainValidationDelegationPayloadError Text |
There is a problem with the delegation payload signature |
ChainValidationInvalidDelegation VerificationKey VerificationKey |
The delegation used in the signature is not valid according to the ledger |
ChainValidationGenesisHashMismatch GenesisHash GenesisHash |
Genesis hash mismatch |
ChainValidationExpectedGenesisHash GenesisHash HeaderHash |
Expected GenesisHash but got HeaderHash |
ChainValidationExpectedHeaderHash HeaderHash GenesisHash |
Expected HeaderHash but GenesisHash |
ChainValidationInvalidHash HeaderHash HeaderHash |
The hash of the previous block does not match the value in the header |
ChainValidationMissingHash HeaderHash |
The hash of the previous block is missing and should be given hash. |
ChainValidationUnexpectedGenesisHash HeaderHash |
There should not be a hash of the previous but there is. |
ChainValidationInvalidSignature BlockSignature |
The signature of the block is invalid |
ChainValidationDelegationSchedulingError Error |
A delegation certificate failed validation in the ledger layer |
ChainValidationProtocolMagicMismatch ProtocolMagicId ProtocolMagicId |
The
|
ChainValidationSignatureLight |
A block is using unsupported lightweight delegation |
ChainValidationTooManyDelegations VerificationKey |
The delegator for this block has delegated in too many recent blocks |
ChainValidationUpdateError SlotNumber Error |
Something failed to register in the update interface |
ChainValidationUTxOValidationError UTxOValidationError |
A transaction failed validation in the ledger layer |
ChainValidationProofValidationError ProofValidationError |
A payload proof did not match. |
Instances
Eq ChainValidationError Source # | |
Defined in Cardano.Chain.Block.Validation (==) :: ChainValidationError -> ChainValidationError -> Bool Source # (/=) :: ChainValidationError -> ChainValidationError -> Bool Source # |
|
Show ChainValidationError Source # | |
Defined in Cardano.Chain.Block.Validation |
UTxO
Size of a heap value, in words
Number of entries in the UTxO
Instances
foldUTxO :: Environment -> UTxO -> Stream ( Of ( ABlock ByteString )) ( ExceptT ParseError ResIO ) () -> ExceptT Error ( ReaderT ValidationMode ResIO ) UTxO Source #
Fold transaction validation over a
Stream
of
Block
s
foldUTxOBlock :: Environment -> UTxO -> ABlock ByteString -> ExceptT Error ( ReaderT ValidationMode ResIO ) UTxO Source #
Fold
updateUTxO
over the transactions in a single
Block
Proof of everything contained in the payload
Proof | |
|
Instances
Eq Proof Source # | |
Show Proof Source # | |
Generic Proof Source # | |
NFData Proof Source # | |
Defined in Cardano.Chain.Block.Proof |
|
ToJSON Proof Source # | |
ToCBOR Proof Source # | |
FromCBOR Proof Source # | |
Buildable Proof Source # | |
NoThunks Proof Source # | |
type Rep Proof Source # | |
Defined in Cardano.Chain.Block.Proof
type
Rep
Proof
=
D1
('
MetaData
"Proof" "Cardano.Chain.Block.Proof" "cardano-ledger-byron-0.1.0.0-1U5kXR8zMRrE7QjCz70XVD" '
False
) (
C1
('
MetaCons
"Proof" '
PrefixI
'
True
) ((
S1
('
MetaSel
('
Just
"proofUTxO") '
NoSourceUnpackedness
'
SourceStrict
'
DecidedStrict
) (
Rec0
TxProof
)
:*:
S1
('
MetaSel
('
Just
"proofSsc") '
NoSourceUnpackedness
'
SourceStrict
'
DecidedStrict
) (
Rec0
SscProof
))
:*:
(
S1
('
MetaSel
('
Just
"proofDelegation") '
NoSourceUnpackedness
'
SourceStrict
'
DecidedStrict
) (
Rec0
(
Hash
Payload
))
:*:
S1
('
MetaSel
('
Just
"proofUpdate") '
NoSourceUnpackedness
'
SourceStrict
'
DecidedStrict
) (
Rec0
Proof
))))
|
data ProofValidationError Source #
Error which can result from attempting to validate an invalid payload proof.
DelegationProofValidationError |
The delegation payload proof did not match |
UTxOProofValidationError |
The UTxO payload proof did not match |
UpdateProofValidationError |
The update payload proof did not match |
Instances
Eq ProofValidationError Source # | |
Defined in Cardano.Chain.Block.Proof (==) :: ProofValidationError -> ProofValidationError -> Bool Source # (/=) :: ProofValidationError -> ProofValidationError -> Bool Source # |
|
Show ProofValidationError Source # | |
Defined in Cardano.Chain.Block.Proof |
recoverProof :: ABody ByteString -> Proof Source #
Header
AHeader | |
|
Instances
Header Constructors
:: ProtocolMagicId | |
-> Either GenesisHash Header | |
-> EpochSlots |
Number of slots per epoch. This is needed to convert the slot number to
the legacy format used in
|
-> SlotNumber | |
-> SigningKey |
The
|
-> Certificate |
A certificate of delegation from a genesis key to the
|
-> Body | |
-> ProtocolVersion | |
-> SoftwareVersion | |
-> Header |
Smart constructor for
Header
:: ProtocolMagicId | |
-> HeaderHash |
Parent |
-> ChainDifficulty | |
-> EpochSlots |
See
|
-> SlotNumber | |
-> SigningKey |
The
|
-> Certificate |
A certificate of delegation from a genesis key to the
|
-> Body | |
-> ProtocolVersion | |
-> SoftwareVersion | |
-> Header |
Make a
Header
for a given slot, with a given body, parent hash,
and difficulty. This takes care of some signing and consensus data.
Header Accessors
headerPrevHash :: AHeader a -> HeaderHash Source #
headerProof :: AHeader a -> Proof Source #
headerSlot :: AHeader a -> SlotNumber Source #
headerIssuer :: AHeader a -> VerificationKey Source #
headerLength :: AHeader ByteString -> Natural Source #
headerDifficulty :: AHeader a -> ChainDifficulty Source #
headerToSign :: EpochSlots -> AHeader a -> ToSign Source #
Header Binary Serialization
toCBORHeader :: EpochSlots -> Header -> Encoding Source #
Encode a header, without taking in to account deprecated epoch boundary blocks.
toCBORHeaderSize :: Proxy EpochSlots -> Proxy ( AHeader a) -> Size Source #
toCBORHeaderToHash :: EpochSlots -> Header -> Encoding Source #
Encode a
Header
accounting for deprecated epoch boundary blocks
This encoding is only used when hashing the header for backwards compatibility, but should not be used when serializing a header within a block
fromCBORAHeader :: EpochSlots -> Decoder s ( AHeader ByteSpan ) Source #
fromCBORHeader :: EpochSlots -> Decoder s Header Source #
fromCBORHeaderToHash :: EpochSlots -> Decoder s ( Maybe Header ) Source #
wrapHeaderBytes :: ByteString -> ByteString Source #
These bytes must be prepended when hashing raw boundary header data
In the Byron release, hashes were taken over a data type that was never directly serialized to the blockchain, so these magic bytes cannot be determined from the raw header data.
These bytes are from `encodeListLen 2 <> toCBOR (1 :: Word8)`
Header Formatting
renderHeader :: EpochSlots -> Header -> Builder Source #
Boundary Header
data ABoundaryHeader a Source #
UnsafeABoundaryHeader | |
|
Instances
mkABoundaryHeader :: Either GenesisHash HeaderHash -> Word64 -> ChainDifficulty -> a -> ABoundaryHeader a Source #
Smart constructor for
ABoundaryHeader
Makes sure that the hash is forced.
toCBORABoundaryHeader :: ProtocolMagicId -> ABoundaryHeader a -> Encoding Source #
Encode from a boundary header with any annotation. This does not
necessarily invert
fromCBORBoundaryHeader
, because that decoder drops
information that this encoder replaces, such as the body proof (assumes
the body is empty) and the extra header data (sets it to empty map).
toCBORABoundaryHeaderSize :: Proxy ProtocolMagicId -> Proxy ( ABoundaryHeader a) -> Size Source #
boundaryHeaderHashAnnotated :: ABoundaryHeader ByteString -> HeaderHash Source #
Compute the hash of a boundary block header from its annotation.
It uses
wrapBoundaryBytes
, for the hash must be computed on the header
bytes tagged with the CBOR list length and tag discriminator, which is
the encoding chosen by cardano-sl.
wrapBoundaryBytes :: ByteString -> ByteString Source #
These bytes must be prepended when hashing raw boundary header data
In the Byron release, hashes were taken over a data type that was never directly serialized to the blockchain, so these magic bytes cannot be determined from the raw header data.
HeaderHash
headerHashF :: Format r ( HeaderHash -> r) Source #
Specialized formatter for
HeaderHash
hashHeader :: EpochSlots -> Header -> HeaderHash Source #
Hash the serialised representation of a
Header
For backwards compatibility we have to take the hash of the header
serialised with
toCBORHeaderToHash
genesisHeaderHash :: GenesisHash -> HeaderHash Source #
Extract the genesis hash and cast it into a header hash.
BlockSignature
type BlockSignature = ABlockSignature () Source #
data ABlockSignature a Source #
Signature of the
Block
We use a heavyweight delegation scheme, so the signature has two parts:
- A delegation certificate from a genesis key to the block signer
-
The actual signature over
ToSign
ABlockSignature | |
|
Instances
ToSign
Data to be signed in
Block
ToSign | |
|
Instances
recoverSignedBytes :: EpochSlots -> AHeader ByteString -> Annotated ToSign ByteString Source #
Produces the ByteString that was signed in the block
fromCBORBoundaryConsensusData :: Decoder s ( Word64 , ChainDifficulty ) Source #
dropBoundaryExtraHeaderDataRetainGenesisTag :: Decoder s Bool Source #
When starting a new chain in ourorobos-consensus, we often start from a non-zero epoch. This is done in order to ensure synchronisation between nodes - we assume that the chain started at some fixed point in the past (e.g. midnight) which all nodes can agree on despite different node start times. However, the standard deserialisation assumes that the genesis EBB is precisely that in epoch zero.
In order to successfully round-trip a genesis EBB in a non-zero epoch, then, we add a "magic" tag which indicates the presense of the genesis hash. The choice of 255 and the word Genesis is completely arbitrary, and only done to correspond with the matching encoder. This encoding will only ever be seen when processing blocks from a demo.
dropBoundaryBody :: Dropper s Source #
Body
consists of payloads of all block components
ABody | |
|
Instances
bodyWitnesses :: Body -> [ TxWitness ] Source #
Block
ABlock | |
|
Instances
Functor ABlock Source # | |
Eq a => Eq ( ABlock a) Source # | |
Show a => Show ( ABlock a) Source # | |
Generic ( ABlock a) Source # | |
NFData a => NFData ( ABlock a) Source # | |
Defined in Cardano.Chain.Block.Block |
|
ToJSON a => ToJSON ( ABlock a) Source # | |
Buildable ( WithEpochSlots Block ) Source # | |
Defined in Cardano.Chain.Block.Block |
|
type Rep ( ABlock a) Source # | |
Defined in Cardano.Chain.Block.Block
type
Rep
(
ABlock
a) =
D1
('
MetaData
"ABlock" "Cardano.Chain.Block.Block" "cardano-ledger-byron-0.1.0.0-1U5kXR8zMRrE7QjCz70XVD" '
False
) (
C1
('
MetaCons
"ABlock" '
PrefixI
'
True
) (
S1
('
MetaSel
('
Just
"blockHeader") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(
AHeader
a))
:*:
(
S1
('
MetaSel
('
Just
"blockBody") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(
ABody
a))
:*:
S1
('
MetaSel
('
Just
"blockAnnotation") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
a))))
|
Block Constructors
:: ProtocolMagicId | |
-> ProtocolVersion | |
-> SoftwareVersion | |
-> Either GenesisHash Header | |
-> EpochSlots | |
-> SlotNumber | |
-> SigningKey |
The
|
-> Certificate |
A certificate of delegation from a genesis key to the
|
-> Body | |
-> Block |
Smart constructor for
Block
:: ProtocolMagicId | |
-> ProtocolVersion | |
-> SoftwareVersion | |
-> HeaderHash | |
-> ChainDifficulty | |
-> EpochSlots | |
-> SlotNumber | |
-> SigningKey |
The
|
-> Certificate |
A certificate of delegation from a genesis key to the
|
-> Body | |
-> Block |
Block Accessors
blockHash :: EpochSlots -> Block -> HeaderHash Source #
blockAProtocolMagicId :: ABlock a -> Annotated ProtocolMagicId a Source #
blockProtocolMagicId :: ABlock a -> ProtocolMagicId Source #
blockPrevHash :: ABlock a -> HeaderHash Source #
blockProof :: ABlock a -> Proof Source #
blockSlot :: ABlock a -> SlotNumber Source #
blockGenesisKey :: ABlock a -> VerificationKey Source #
blockIssuer :: ABlock a -> VerificationKey Source #
blockDifficulty :: ABlock a -> ChainDifficulty Source #
blockToSign :: EpochSlots -> ABlock a -> ToSign Source #
blockSignature :: ABlock a -> ABlockSignature a Source #
blockProtocolVersion :: ABlock a -> ProtocolVersion Source #
blockSoftwareVersion :: ABlock a -> SoftwareVersion Source #
blockTxPayload :: ABlock a -> ATxPayload a Source #
blockSscPayload :: ABlock a -> SscPayload Source #
blockDlgPayload :: ABlock a -> APayload a Source #
blockUpdatePayload :: ABlock a -> APayload a Source #
blockLength :: ABlock ByteString -> Natural Source #
Block Binary Serialization
toCBORBlock :: EpochSlots -> Block -> Encoding Source #
Encode a block, given a number of slots-per-epoch.
Unlike
toCBORABOBBlock
, this function does not take the deprecated epoch
boundary blocks into account.
fromCBORABlock :: EpochSlots -> Decoder s ( ABlock ByteSpan ) Source #
Block Formatting
renderBlock :: EpochSlots -> Block -> Builder Source #
ABlockOrBoundary
data ABlockOrBoundary a Source #
ABOBBlock ( ABlock a) | |
ABOBBoundary ( ABoundaryBlock a) |
Instances
toCBORABOBBlock :: EpochSlots -> ABlock a -> Encoding Source #
Encode a
Block
accounting for deprecated epoch boundary blocks
fromCBORABOBBlock :: EpochSlots -> Decoder s ( Maybe Block ) Source #
Decode a
Block
accounting for deprecated epoch boundary blocks
fromCBORABlockOrBoundary :: EpochSlots -> Decoder s ( ABlockOrBoundary ByteSpan ) Source #
Decode a
Block
accounting for deprecated epoch boundary blocks
Previous versions of Cardano had an explicit boundary block between epochs.
A
Block
was then represented as 'Either BoundaryBlock MainBlock'. We have
now deprecated these explicit boundary blocks, but we still need to decode
blocks in the old format. In the case that we find a boundary block, we
drop it using
dropBoundaryBlock
and return a
Nothing
.
toCBORABlockOrBoundary :: ProtocolMagicId -> EpochSlots -> ABlockOrBoundary a -> Encoding Source #
ABoundaryBlock
data ABoundaryBlock a Source #
For a boundary block, we keep the header, body, and an annotation for the whole thing (commonly the bytes from which it was decoded).
ABoundaryBlock | |
|
Instances
boundaryHashAnnotated :: ABoundaryBlock ByteString -> HeaderHash Source #
Extract the hash of a boundary block from its annotation.
toCBORABoundaryBlock :: ProtocolMagicId -> ABoundaryBlock a -> Encoding Source #
See note on
toCBORABoundaryHeader
. This as well does not necessarily
invert the decoder
fromCBORABoundaryBlock
.
toCBORABOBBoundary :: ProtocolMagicId -> ABoundaryBlock a -> Encoding Source #
toCBORABoundaryBlock but with the list length and tag discriminator bytes.
:: EpochSlots | |
-> Word64 |
Epoch number |
-> SlotNumber |
Compute the slot number assigned to a boundary block
data ABoundaryBody a Source #
For boundary body data, we only keep an annotation. It's the body and extra body data.
Instances
ABlockOrBoundaryHdr
data ABlockOrBoundaryHdr a Source #
ABOBBlockHdr !( AHeader a) | |
ABOBBoundaryHdr !( ABoundaryHeader a) |
Instances
aBlockOrBoundaryHdr :: ( AHeader a -> b) -> ( ABoundaryHeader a -> b) -> ABlockOrBoundaryHdr a -> b Source #
The analogue of
either
toCBORABlockOrBoundaryHdr :: ABlockOrBoundaryHdr ByteString -> Encoding Source #
Encoder for
ABlockOrBoundaryHdr
which is using the annotation.
It is right inverse of
fromCBORAblockOrBoundaryHdr
.
TODO: add a round trip test, e.g.
fromCBORABlockOrBoundaryHdr . toCBORABlockOrBoundaryHdr = id
which does not type check, but convey the meaning.
toCBORABlockOrBoundaryHdrSize :: Proxy ( ABlockOrBoundaryHdr a) -> Size Source #
The size computation is compatible with
toCBORABlockOrBoundaryHdr
abobHdrSlotNo :: EpochSlots -> ABlockOrBoundaryHdr a -> SlotNumber Source #
Slot number of the header
NOTE: Epoch slot number calculation must match the one in
applyBoundary
.