Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type CardanoEras c = ByronBlock ': CardanoShelleyEras c
- type CardanoShelleyEras c = '[ShelleyBlock (TPraos c) (ShelleyEra c), ShelleyBlock (TPraos c) (AllegraEra c), ShelleyBlock (TPraos c) (MaryEra c), ShelleyBlock (TPraos c) (AlonzoEra c), ShelleyBlock (Praos c) (BabbageEra c), ShelleyBlock (Praos c) (ConwayEra c)]
- module Ouroboros.Consensus.Shelley.Eras
- type ShelleyBasedLedgerEras c = '[ShelleyEra c, AllegraEra c, MaryEra c, AlonzoEra c, BabbageEra c, ConwayEra c]
- type CardanoBlock c = HardForkBlock (CardanoEras c)
- data HardForkBlock (xs ∷ [Type]) where
- pattern BlockAllegra ∷ ShelleyBlock (TPraos c) (AllegraEra c) → CardanoBlock c
- pattern BlockAlonzo ∷ ShelleyBlock (TPraos c) (AlonzoEra c) → CardanoBlock c
- pattern BlockByron ∷ ByronBlock → CardanoBlock c
- pattern BlockMary ∷ ShelleyBlock (TPraos c) (MaryEra c) → CardanoBlock c
- pattern BlockShelley ∷ ShelleyBlock (TPraos c) (ShelleyEra c) → CardanoBlock c
- pattern BlockBabbage ∷ ShelleyBlock (Praos c) (BabbageEra c) → CardanoBlock c
- pattern BlockConway ∷ ShelleyBlock (Praos c) (ConwayEra c) → CardanoBlock c
- type CardanoHeader c = Header (CardanoBlock c)
- data family Header blk
- type CardanoApplyTxErr c = HardForkApplyTxErr (CardanoEras c)
- type CardanoGenTx c = GenTx (CardanoBlock c)
- type CardanoGenTxId c = GenTxId (CardanoBlock c)
- data family GenTx blk
- data HardForkApplyTxErr (xs ∷ [Type]) where
- pattern ApplyTxErrAllegra ∷ ApplyTxErr (ShelleyBlock (TPraos c) (AllegraEra c)) → CardanoApplyTxErr c
- pattern ApplyTxErrAlonzo ∷ ApplyTxErr (ShelleyBlock (TPraos c) (AlonzoEra c)) → CardanoApplyTxErr c
- pattern ApplyTxErrByron ∷ ApplyTxErr ByronBlock → CardanoApplyTxErr c
- pattern ApplyTxErrMary ∷ ApplyTxErr (ShelleyBlock (TPraos c) (MaryEra c)) → CardanoApplyTxErr c
- pattern ApplyTxErrShelley ∷ ApplyTxErr (ShelleyBlock (TPraos c) (ShelleyEra c)) → CardanoApplyTxErr c
- pattern ApplyTxErrWrongEra ∷ EraMismatch → CardanoApplyTxErr c
- pattern ApplyTxErrBabbage ∷ ApplyTxErr (ShelleyBlock (Praos c) (BabbageEra c)) → CardanoApplyTxErr c
- pattern ApplyTxErrConway ∷ ApplyTxErr (ShelleyBlock (Praos c) (ConwayEra c)) → CardanoApplyTxErr c
- data family TxId tx
- type CardanoLedgerError c = HardForkLedgerError (CardanoEras c)
- data HardForkLedgerError (xs ∷ [Type]) where
- pattern LedgerErrorAllegra ∷ LedgerError (ShelleyBlock (TPraos c) (AllegraEra c)) → CardanoLedgerError c
- pattern LedgerErrorAlonzo ∷ LedgerError (ShelleyBlock (TPraos c) (AlonzoEra c)) → CardanoLedgerError c
- pattern LedgerErrorByron ∷ LedgerError ByronBlock → CardanoLedgerError c
- pattern LedgerErrorMary ∷ LedgerError (ShelleyBlock (TPraos c) (MaryEra c)) → CardanoLedgerError c
- pattern LedgerErrorShelley ∷ LedgerError (ShelleyBlock (TPraos c) (ShelleyEra c)) → CardanoLedgerError c
- pattern LedgerErrorWrongEra ∷ EraMismatch → CardanoLedgerError c
- pattern LedgerErrorBabbage ∷ LedgerError (ShelleyBlock (Praos c) (BabbageEra c)) → CardanoLedgerError c
- pattern LedgerErrorConway ∷ LedgerError (ShelleyBlock (Praos c) (ConwayEra c)) → CardanoLedgerError c
- type CardanoOtherHeaderEnvelopeError c = HardForkEnvelopeErr (CardanoEras c)
- data HardForkEnvelopeErr (xs ∷ [Type]) where
- pattern OtherHeaderEnvelopeErrorAllegra ∷ OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (AllegraEra c)) → CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorBabbage ∷ OtherHeaderEnvelopeError (ShelleyBlock (Praos c) (BabbageEra c)) → CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorConway ∷ OtherHeaderEnvelopeError (ShelleyBlock (Praos c) (ConwayEra c)) → CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorAlonzo ∷ OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (AlonzoEra c)) → CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorByron ∷ OtherHeaderEnvelopeError ByronBlock → CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorMary ∷ OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (MaryEra c)) → CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorShelley ∷ OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (ShelleyEra c)) → CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorWrongEra ∷ EraMismatch → CardanoOtherHeaderEnvelopeError c
- type CardanoTipInfo c = OneEraTipInfo (CardanoEras c)
- data OneEraTipInfo (xs ∷ [Type]) where
- pattern TipInfoAllegra ∷ TipInfo (ShelleyBlock (TPraos c) (AllegraEra c)) → CardanoTipInfo c
- pattern TipInfoAlonzo ∷ TipInfo (ShelleyBlock (TPraos c) (AlonzoEra c)) → CardanoTipInfo c
- pattern TipInfoByron ∷ TipInfo ByronBlock → CardanoTipInfo c
- pattern TipInfoBabbage ∷ TipInfo (ShelleyBlock (Praos c) (BabbageEra c)) → CardanoTipInfo c
- pattern TipInfoConway ∷ TipInfo (ShelleyBlock (Praos c) (ConwayEra c)) → CardanoTipInfo c
- pattern TipInfoMary ∷ TipInfo (ShelleyBlock (TPraos c) (MaryEra c)) → CardanoTipInfo c
- pattern TipInfoShelley ∷ TipInfo (ShelleyBlock (TPraos c) (ShelleyEra c)) → CardanoTipInfo c
- data family BlockQuery blk ∷ Type → Type
- type CardanoQuery c = BlockQuery (CardanoBlock c)
- type CardanoQueryResult c = HardForkQueryResult (CardanoEras c)
- data Either a b where
- pattern QueryResultSuccess ∷ result → CardanoQueryResult c result
- pattern QueryResultEraMismatch ∷ EraMismatch → CardanoQueryResult c result
- type CardanoCodecConfig c = CodecConfig (CardanoBlock c)
- data family CodecConfig blk
- data family BlockConfig blk
- type CardanoBlockConfig c = BlockConfig (CardanoBlock c)
- type CardanoStorageConfig c = StorageConfig (CardanoBlock c)
- data family StorageConfig blk
- type CardanoConsensusConfig c = ConsensusConfig (HardForkProtocol (CardanoEras c))
- data family ConsensusConfig p
- type CardanoLedgerConfig c = HardForkLedgerConfig (CardanoEras c)
- data HardForkLedgerConfig (xs ∷ [Type]) where
- pattern CardanoLedgerConfig ∷ PartialLedgerConfig ByronBlock → PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c)) → PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c)) → PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c)) → PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c)) → PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c)) → PartialLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c)) → CardanoLedgerConfig c
- type CardanoLedgerState c = LedgerState (CardanoBlock c)
- data family LedgerState blk
- type CardanoChainDepState c = HardForkChainDepState (CardanoEras c)
- data HardForkState (f ∷ Type → Type) (xs ∷ [Type]) where
- pattern ChainDepStateAllegra ∷ ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c))) → CardanoChainDepState c
- pattern ChainDepStateAlonzo ∷ ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c))) → CardanoChainDepState c
- pattern ChainDepStateBabbage ∷ ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c))) → CardanoChainDepState c
- pattern ChainDepStateConway ∷ ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c))) → CardanoChainDepState c
- pattern ChainDepStateByron ∷ ChainDepState (BlockProtocol ByronBlock) → CardanoChainDepState c
- pattern ChainDepStateMary ∷ ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c))) → CardanoChainDepState c
- pattern ChainDepStateShelley ∷ ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))) → CardanoChainDepState c
- data EraMismatch = EraMismatch {}
Eras
type CardanoEras c = ByronBlock ': CardanoShelleyEras c Source #
The eras in the Cardano blockchain.
We parameterise over the crypto used in the post-Byron eras: c
.
TODO: parameterise ByronBlock over crypto too
type CardanoShelleyEras c = '[ShelleyBlock (TPraos c) (ShelleyEra c), ShelleyBlock (TPraos c) (AllegraEra c), ShelleyBlock (TPraos c) (MaryEra c), ShelleyBlock (TPraos c) (AlonzoEra c), ShelleyBlock (Praos c) (BabbageEra c), ShelleyBlock (Praos c) (ConwayEra c)] Source #
type ShelleyBasedLedgerEras c = '[ShelleyEra c, AllegraEra c, MaryEra c, AlonzoEra c, BabbageEra c, ConwayEra c] Source #
Block
type CardanoBlock c = HardForkBlock (CardanoEras c) Source #
The Cardano block.
Thanks to the pattern synonyms, you can treat this as a sum type with
constructors BlockByron
, BlockShelley
, etc.
f :: CardanoBlock c -> _ f (BlockByron b) = _ f (BlockShelley s) = _ f (BlockAllegra a) = _ f (BlockMary m) = _ f (BlockAlonzo m) = _
data HardForkBlock (xs ∷ [Type]) where Source #
pattern BlockAllegra ∷ ShelleyBlock (TPraos c) (AllegraEra c) → CardanoBlock c | |
pattern BlockAlonzo ∷ ShelleyBlock (TPraos c) (AlonzoEra c) → CardanoBlock c | |
pattern BlockByron ∷ ByronBlock → CardanoBlock c | |
pattern BlockMary ∷ ShelleyBlock (TPraos c) (MaryEra c) → CardanoBlock c | |
pattern BlockShelley ∷ ShelleyBlock (TPraos c) (ShelleyEra c) → CardanoBlock c | |
pattern BlockBabbage ∷ ShelleyBlock (Praos c) (BabbageEra c) → CardanoBlock c | |
pattern BlockConway ∷ ShelleyBlock (Praos c) (ConwayEra c) → CardanoBlock c |
Instances
Headers
type CardanoHeader c = Header (CardanoBlock c) Source #
The Cardano header.
data family Header blk Source #
Instances
Generalised transactions
type CardanoApplyTxErr c = HardForkApplyTxErr (CardanoEras c) Source #
An error resulting from applying a CardanoGenTx
to the ledger.
Thanks to the pattern synonyms, you can treat this as a sum type with
constructors ApplyTxByronErr
, ApplyTxErrShelley
, and
ApplyTxErrWrongEra
.
toText :: CardanoApplyTxErr c -> Text toText (ApplyTxErrByron b) = byronApplyTxErrToText b toText (ApplyTxErrShelley s) = shelleyApplyTxErrToText s toText (ApplyTxErrAllegra a) = allegraApplyTxErrToText a toText (ApplyTxErrMary m) = maryApplyTxErrToText m toText (ApplyTxErrWrongEra eraMismatch) = "Transaction from the " <> otherEraName eraMismatch <> " era applied to a ledger from the " <> ledgerEraName eraMismatch <> " era"
type CardanoGenTx c = GenTx (CardanoBlock c) Source #
The Cardano transaction.
type CardanoGenTxId c = GenTxId (CardanoBlock c) Source #
The ID of a Cardano transaction.
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
data HardForkApplyTxErr (xs ∷ [Type]) where Source #
pattern ApplyTxErrAllegra ∷ ApplyTxErr (ShelleyBlock (TPraos c) (AllegraEra c)) → CardanoApplyTxErr c | |
pattern ApplyTxErrAlonzo ∷ ApplyTxErr (ShelleyBlock (TPraos c) (AlonzoEra c)) → CardanoApplyTxErr c | |
pattern ApplyTxErrByron ∷ ApplyTxErr ByronBlock → CardanoApplyTxErr c | |
pattern ApplyTxErrMary ∷ ApplyTxErr (ShelleyBlock (TPraos c) (MaryEra c)) → CardanoApplyTxErr c | |
pattern ApplyTxErrShelley ∷ ApplyTxErr (ShelleyBlock (TPraos c) (ShelleyEra c)) → CardanoApplyTxErr c | |
pattern ApplyTxErrWrongEra ∷ EraMismatch → CardanoApplyTxErr c | |
pattern ApplyTxErrBabbage ∷ ApplyTxErr (ShelleyBlock (Praos c) (BabbageEra c)) → CardanoApplyTxErr c | |
pattern ApplyTxErrConway ∷ ApplyTxErr (ShelleyBlock (Praos c) (ConwayEra c)) → CardanoApplyTxErr c |
Instances
A generalized transaction, GenTx
, identifier.
Instances
LedgerError
type CardanoLedgerError c = HardForkLedgerError (CardanoEras c) Source #
An error resulting from applying a CardanoBlock
to the ledger.
Thanks to the pattern synonyms, you can treat this as a sum type with
constructors LedgerErrorByron
, LedgerErrorShelley
, and
LedgerErrorWrongEra
.
toText :: CardanoLedgerError c -> Text toText (LedgerErrorByron b) = byronLedgerErrorToText b toText (LedgerErrorShelley s) = shelleyLedgerErrorToText s toText (LedgerErrorAllegra a) = allegraLedgerErrorToText a toText (LedgerErrorMary m) = maryLedgerErrorToText m toText (LedgerErrorWrongEra eraMismatch) = "Block from the " <> otherEraName eraMismatch <> " era applied to a ledger from the " <> ledgerEraName eraMismatch <> " era"
data HardForkLedgerError (xs ∷ [Type]) where Source #
pattern LedgerErrorAllegra ∷ LedgerError (ShelleyBlock (TPraos c) (AllegraEra c)) → CardanoLedgerError c | |
pattern LedgerErrorAlonzo ∷ LedgerError (ShelleyBlock (TPraos c) (AlonzoEra c)) → CardanoLedgerError c | |
pattern LedgerErrorByron ∷ LedgerError ByronBlock → CardanoLedgerError c | |
pattern LedgerErrorMary ∷ LedgerError (ShelleyBlock (TPraos c) (MaryEra c)) → CardanoLedgerError c | |
pattern LedgerErrorShelley ∷ LedgerError (ShelleyBlock (TPraos c) (ShelleyEra c)) → CardanoLedgerError c | |
pattern LedgerErrorWrongEra ∷ EraMismatch → CardanoLedgerError c | |
pattern LedgerErrorBabbage ∷ LedgerError (ShelleyBlock (Praos c) (BabbageEra c)) → CardanoLedgerError c | |
pattern LedgerErrorConway ∷ LedgerError (ShelleyBlock (Praos c) (ConwayEra c)) → CardanoLedgerError c |
Instances
OtherEnvelopeError
type CardanoOtherHeaderEnvelopeError c = HardForkEnvelopeErr (CardanoEras c) Source #
An error resulting from validating a CardanoHeader
.
data HardForkEnvelopeErr (xs ∷ [Type]) where Source #
Instances
TipInfo
type CardanoTipInfo c = OneEraTipInfo (CardanoEras c) Source #
The TipInfo
of the Cardano chain.
data OneEraTipInfo (xs ∷ [Type]) where Source #
pattern TipInfoAllegra ∷ TipInfo (ShelleyBlock (TPraos c) (AllegraEra c)) → CardanoTipInfo c | |
pattern TipInfoAlonzo ∷ TipInfo (ShelleyBlock (TPraos c) (AlonzoEra c)) → CardanoTipInfo c | |
pattern TipInfoByron ∷ TipInfo ByronBlock → CardanoTipInfo c | |
pattern TipInfoBabbage ∷ TipInfo (ShelleyBlock (Praos c) (BabbageEra c)) → CardanoTipInfo c | |
pattern TipInfoConway ∷ TipInfo (ShelleyBlock (Praos c) (ConwayEra c)) → CardanoTipInfo c | |
pattern TipInfoMary ∷ TipInfo (ShelleyBlock (TPraos c) (MaryEra c)) → CardanoTipInfo c | |
pattern TipInfoShelley ∷ TipInfo (ShelleyBlock (TPraos c) (ShelleyEra c)) → CardanoTipInfo c |
Instances
CanHardFork xs ⇒ Show (OneEraTipInfo xs) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras showsPrec ∷ Int → OneEraTipInfo xs → ShowS # show ∷ OneEraTipInfo xs → String # showList ∷ [OneEraTipInfo xs] → ShowS # | |
CanHardFork xs ⇒ Eq (OneEraTipInfo xs) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras (==) ∷ OneEraTipInfo xs → OneEraTipInfo xs → Bool # (/=) ∷ OneEraTipInfo xs → OneEraTipInfo xs → Bool # | |
CanHardFork xs ⇒ NoThunks (OneEraTipInfo xs) | |
Query
data family BlockQuery blk ∷ Type → Type Source #
Different queries supported by the ledger, indexed by the result type.
Instances
type CardanoQuery c = BlockQuery (CardanoBlock c) Source #
The Query
of Cardano chain.
type CardanoQueryResult c = HardForkQueryResult (CardanoEras c) Source #
The result of a CardanoQuery
Thanks to the pattern synonyms, you can treat this as a sum type with
constructors QueryResultSuccess
and QueryResultEraMismatch
.
The Either
type represents values with two possibilities: a value of
type
is either Either
a b
or Left
a
.Right
b
The Either
type is sometimes used to represent a value which is
either correct or an error; by convention, the Left
constructor is
used to hold an error value and the Right
constructor is used to
hold a correct value (mnemonic: "right" also means "correct").
Examples
The type
is the type of values which can be either
a Either
String
Int
String
or an Int
. The Left
constructor can be used only on
String
s, and the Right
constructor can be used only on Int
s:
>>>
let s = Left "foo" :: Either String Int
>>>
s
Left "foo">>>
let n = Right 3 :: Either String Int
>>>
n
Right 3>>>
:type s
s :: Either String Int>>>
:type n
n :: Either String Int
The fmap
from our Functor
instance will ignore Left
values, but
will apply the supplied function to values contained in a Right
:
>>>
let s = Left "foo" :: Either String Int
>>>
let n = Right 3 :: Either String Int
>>>
fmap (*2) s
Left "foo">>>
fmap (*2) n
Right 6
The Monad
instance for Either
allows us to chain together multiple
actions which may fail, and fail overall if any of the individual
steps failed. First we'll write a function that can either parse an
Int
from a Char
, or fail.
>>>
import Data.Char ( digitToInt, isDigit )
>>>
:{
let parseEither :: Char -> Either String Int parseEither c | isDigit c = Right (digitToInt c) | otherwise = Left "parse error">>>
:}
The following should work, since both '1'
and '2'
can be
parsed as Int
s.
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Right 3
But the following should fail overall, since the first operation where
we attempt to parse 'm'
as an Int
will fail:
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither 'm' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Left "parse error"
pattern QueryResultSuccess ∷ result → CardanoQueryResult c result | |
pattern QueryResultEraMismatch ∷ EraMismatch → CardanoQueryResult c result | A query from a different era than the ledger's era was sent. |
Instances
CodecConfig
type CardanoCodecConfig c = CodecConfig (CardanoBlock c) Source #
The CodecConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of
the Byron, Shelley, ... CodecConfig
s.
data family CodecConfig blk Source #
Static configuration required for serialisation and deserialisation of types pertaining to this type of block.
Data family instead of type family to get better type inference.
Instances
BlockConfig
data family BlockConfig blk Source #
Static configuration required to work with this type of blocks
Instances
type CardanoBlockConfig c = BlockConfig (CardanoBlock c) Source #
The BlockConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of
the Byron, Shelley, ... BlockConfig
s.
StorageConfig
type CardanoStorageConfig c = StorageConfig (CardanoBlock c) Source #
The StorageConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of
the Byron, Shelley, ... StorageConfig
s.
data family StorageConfig blk Source #
Config needed for the
NodeInitStorage
class. Defined here to
avoid circular dependencies.
Instances
ConsensusConfig
type CardanoConsensusConfig c = ConsensusConfig (HardForkProtocol (CardanoEras c)) Source #
The ConsensusConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of the
Byron, Shelley, ... PartialConsensusConfig
s.
NOTE: not ConsensusConfig
, but PartialConsensusConfig
.
data family ConsensusConfig p Source #
Static configuration required to run the consensus protocol
Every method in the ConsensusProtocol
class takes the consensus
configuration as a parameter, so having this as a data family rather than a
type family resolves most ambiguity.
Defined out of the class so that protocols can define this type without having to define the entire protocol at the same time (or indeed in the same module).
Instances
LedgerConfig
type CardanoLedgerConfig c = HardForkLedgerConfig (CardanoEras c) Source #
The LedgerConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of the
Byron, Shelley, ... PartialLedgerConfig
s.
NOTE: not LedgerConfig
, but PartialLedgerConfig
.
data HardForkLedgerConfig (xs ∷ [Type]) where Source #
pattern CardanoLedgerConfig ∷ PartialLedgerConfig ByronBlock → PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c)) → PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c)) → PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c)) → PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c)) → PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c)) → PartialLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c)) → CardanoLedgerConfig c |
Instances
Generic (HardForkLedgerConfig xs) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics type Rep (HardForkLedgerConfig xs) ∷ Type → Type # from ∷ HardForkLedgerConfig xs → Rep (HardForkLedgerConfig xs) x # to ∷ Rep (HardForkLedgerConfig xs) x → HardForkLedgerConfig xs # | |
CanHardFork xs ⇒ NoThunks (HardForkLedgerConfig xs) | |
type Rep (HardForkLedgerConfig xs) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics type Rep (HardForkLedgerConfig xs) = D1 ('MetaData "HardForkLedgerConfig" "Ouroboros.Consensus.HardFork.Combinator.Basics" "ouroboros-consensus-0.21.0.0-inplace" 'False) (C1 ('MetaCons "HardForkLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "hardForkLedgerConfigShape") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Shape xs)) :*: S1 ('MetaSel ('Just "hardForkLedgerConfigPerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PerEraLedgerConfig xs)))) |
LedgerState
type CardanoLedgerState c = LedgerState (CardanoBlock c) Source #
The LedgerState
for CardanoBlock
.
NOTE: the CardanoLedgerState
contains more than just the current era's
LedgerState
. We don't give access to those internal details through the
pattern synonyms. This is also the reason the pattern synonyms are not
bidirectional.
data family LedgerState blk Source #
Ledger state associated with a block
This is the Consensus notion of a ledger state. Each block type is
associated with one of the Ledger types for the ledger state. Virtually
every concept in this codebase revolves around this type, or the referenced
blk
. Whenever we use the type variable l
, we intend to denote that the
expected instantiation is either a LedgerState
or some wrapper over it
(like the ExtLedgerState
).
The main operations we can do with a LedgerState
are ticking (defined in
IsLedger
), and applying a block (defined in
ApplyBlock
).
Instances
ChainDepState
type CardanoChainDepState c = HardForkChainDepState (CardanoEras c) Source #
The ChainDepState
for CardanoBlock
.
NOTE: the CardanoChainDepState
contains more than just the current era's
ChainDepState
. We don't give access to those internal details through the
pattern synonyms. This is also the reason the pattern synonyms are not
bidirectional.
data HardForkState (f ∷ Type → Type) (xs ∷ [Type]) where Source #
Generic hard fork state
This is used both for the consensus state and the ledger state.
By using a telescope with f ~ LedgerState
, we will keep track of Past
information for eras before the current one:
TZ currentByronState TZ pastByronState $ TZ currentShelleyState TZ pastByronState $ TS pastShelleyState $ TZ currentAllegraState ...
These are some intuitions on how the Telescope operations behave for this type:
extend
Suppose we have a telescope containing the ledger state. The "how to extend" argument would take, say, the final Byron state to the initial Shelley state; and "where to extend from" argument would indicate when we want to extend: when the current slot number has gone past the end of the Byron era.
retract
Suppose we have a telescope containing the consensus state. When we rewind
the consensus state, we might cross a hard fork transition point. So we first
retract the telescope to the era containing the slot number that we want
to rewind to, and only then call rewindChainDepState
on that era. Of course,
retraction may fail (we might not have past consensus state to rewind to
anymore); this failure would require a choice for a particular monad m
.
align
Suppose we have one telescope containing the already-ticked ledger state, and
another telescope containing the consensus state. Since the ledger state has
already been ticked, it might have been advanced to the next era. If this
happens, we should then align the consensus state with the ledger state,
moving it also to the next era, before we can do the consensus header
validation check. Note that in this particular example, the ledger state will
always be ahead of the consensus state, never behind; alignExtend
can be
used in this case.
pattern ChainDepStateAllegra ∷ ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c))) → CardanoChainDepState c | |
pattern ChainDepStateAlonzo ∷ ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c))) → CardanoChainDepState c | |
pattern ChainDepStateBabbage ∷ ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c))) → CardanoChainDepState c | |
pattern ChainDepStateConway ∷ ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c))) → CardanoChainDepState c | |
pattern ChainDepStateByron ∷ ChainDepState (BlockProtocol ByronBlock) → CardanoChainDepState c | |
pattern ChainDepStateMary ∷ ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c))) → CardanoChainDepState c | |
pattern ChainDepStateShelley ∷ ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))) → CardanoChainDepState c |
Instances
type Prod HardForkState | |
type SListIN HardForkState | |
type CollapseTo HardForkState a | |
type AllN HardForkState (c ∷ Type → Constraint) | |
type Same HardForkState | |
data Ticked (HardForkChainDepState xs) | |
EraMismatch
data EraMismatch Source #
Extra info for errors caused by applying a block, header, transaction, or query from one era to a ledger from a different era.
EraMismatch | |
|