Safe Haskell | None |
---|---|
Language | Haskell2010 |
Ouroboros.Consensus.HardFork.Combinator
Description
The hard fork combinator
Intended for unqualified import
Synopsis
- type Except e = ExceptT e Identity
-
data
EpochInfo
(m ::
Type
->
Type
) =
EpochInfo
{
- epochInfoSize_ :: HasCallStack => EpochNo -> m EpochSize
- epochInfoFirst_ :: HasCallStack => EpochNo -> m SlotNo
- epochInfoEpoch_ :: HasCallStack => SlotNo -> m EpochNo
- epochInfoSlotToRelativeTime_ :: HasCallStack => SlotNo -> m RelativeTime
- epochInfoSlotLength_ :: HasCallStack => SlotNo -> m SlotLength
-
newtype
LedgerEraInfo
blk =
LedgerEraInfo
{
- getLedgerEraInfo :: SingleEraInfo blk
-
data
SingleEraInfo
blk =
SingleEraInfo
{
- singleEraName :: ! Text
- data Product2 f g x y = Pair2 (f x y) (g x y)
- data family Ticked st :: Type
- data family NestedCtxt_ blk :: ( Type -> Type ) -> Type -> Type
- data family Header blk :: Type
- data family StorageConfig blk :: Type
- data family CodecConfig blk :: Type
- data family BlockConfig blk :: Type
- data family ConsensusConfig p :: Type
- data family LedgerState blk :: Type
- data family Validated x :: Type
- data family TxId tx :: Type
- data family GenTx blk :: Type
-
class
IsNonEmpty
xs
where
- isNonEmpty :: proxy xs -> ProofNonEmpty xs
-
data
ProofNonEmpty
:: [a] ->
Type
where
- ProofNonEmpty :: Proxy x -> Proxy xs -> ProofNonEmpty (x ': xs)
- data PastHorizonException
- newtype WrapPartialConsensusConfig blk = WrapPartialConsensusConfig { }
- newtype WrapPartialLedgerConfig blk = WrapPartialLedgerConfig { }
-
class
(
UpdateLedger
blk,
NoThunks
(
PartialLedgerConfig
blk)) =>
HasPartialLedgerConfig
blk
where
- type PartialLedgerConfig blk :: Type
- completeLedgerConfig :: proxy blk -> EpochInfo ( Except PastHorizonException ) -> PartialLedgerConfig blk -> LedgerConfig blk
-
class
(
ConsensusProtocol
p,
NoThunks
(
PartialConsensusConfig
p)) =>
HasPartialConsensusConfig
p
where
- type PartialConsensusConfig p :: Type
- completeConsensusConfig :: proxy p -> EpochInfo ( Except PastHorizonException ) -> PartialConsensusConfig p -> ConsensusConfig p
- toPartialConsensusConfig :: proxy p -> ConsensusConfig p -> PartialConsensusConfig p
- data InPairs (f :: k -> k -> Type ) (xs :: [k]) where
- data Telescope (g :: k -> Type ) (f :: k -> Type ) (xs :: [k]) where
- data Mismatch :: (k -> Type ) -> (k -> Type ) -> [k] -> Type where
-
newtype
HardForkState
f xs =
HardForkState
{
- getHardForkState :: Telescope ( K Past ) ( Current f) xs
-
data
EraTranslation
xs =
EraTranslation
{
- translateLedgerState :: InPairs ( RequiringBoth WrapLedgerConfig ( Translate LedgerState )) xs
- translateChainDepState :: InPairs ( RequiringBoth WrapConsensusConfig ( Translate WrapChainDepState )) xs
- translateLedgerView :: InPairs ( RequiringBoth WrapLedgerConfig ( TranslateForecast LedgerState WrapLedgerView )) xs
- trivialEraTranslation :: EraTranslation '[blk]
- type InjectValidatedTx = InjectPolyTx WrapValidatedGenTx
- type InjectTx = InjectPolyTx GenTx
- pattern InjectValidatedTx :: ( WrapValidatedGenTx blk -> Maybe ( WrapValidatedGenTx blk')) -> InjectValidatedTx blk blk'
- pattern InjectTx :: ( GenTx blk -> Maybe ( GenTx blk')) -> InjectTx blk blk'
- cannotInjectTx :: InjectTx blk blk'
- cannotInjectValidatedTx :: InjectValidatedTx blk blk'
- data family BlockQuery blk :: Type -> Type
-
newtype
EraIndex
xs =
EraIndex
{
- getEraIndex :: NS ( K ()) xs
-
class
(
LedgerSupportsProtocol
blk,
InspectLedger
blk,
LedgerSupportsMempool
blk,
HasTxId
(
GenTx
blk),
QueryLedger
blk,
HasPartialConsensusConfig
(
BlockProtocol
blk),
HasPartialLedgerConfig
blk,
ConvertRawHash
blk,
ReconstructNestedCtxt
Header
blk,
CommonProtocolParams
blk,
LedgerSupportsPeerSelection
blk,
ConfigSupportsNode
blk,
NodeInitStorage
blk,
BlockSupportsMetrics
blk,
Eq
(
GenTx
blk),
Eq
(
Validated
(
GenTx
blk)),
Eq
(
ApplyTxErr
blk),
Show
blk,
Show
(
Header
blk),
Show
(
CannotForge
blk),
Show
(
ForgeStateInfo
blk),
Show
(
ForgeStateUpdateError
blk)) =>
SingleEraBlock
blk
where
- singleEraTransition :: PartialLedgerConfig blk -> EraParams -> Bound -> LedgerState blk -> Maybe EpochNo
- singleEraInfo :: proxy blk -> SingleEraInfo blk
- proxySingle :: Proxy SingleEraBlock
- singleEraTransition' :: SingleEraBlock blk => WrapPartialLedgerConfig blk -> EraParams -> Bound -> LedgerState blk -> Maybe EpochNo
- eraIndexEmpty :: EraIndex '[] -> Void
- eraIndexFromNS :: SListI xs => NS f xs -> EraIndex xs
- eraIndexFromIndex :: Index xs blk -> EraIndex xs
- eraIndexZero :: EraIndex (x ': xs)
- eraIndexSucc :: EraIndex xs -> EraIndex (x ': xs)
- eraIndexToInt :: EraIndex xs -> Int
- initHardForkState :: f x -> HardForkState f (x ': xs)
-
data
WithBlockNo
(f :: k ->
Type
) (a :: k) =
WithBlockNo
{
- getBlockNo :: BlockNo
- dropBlockNo :: f a
-
data
AcrossEraSelection
::
Type
->
Type
->
Type
where
- CompareBlockNo :: AcrossEraSelection x y
- SelectSameProtocol :: BlockProtocol x ~ BlockProtocol y => AcrossEraSelection x y
- CustomChainSel :: ( SelectView ( BlockProtocol x) -> SelectView ( BlockProtocol y) -> Ordering ) -> AcrossEraSelection x y
- acrossEraSelection :: All SingleEraBlock xs => Tails AcrossEraSelection xs -> WithBlockNo ( NS WrapSelectView ) xs -> WithBlockNo ( NS WrapSelectView ) xs -> Ordering
- mapWithBlockNo :: (f x -> g y) -> WithBlockNo f x -> WithBlockNo g y
-
class
SingleEraBlock
blk =>
NoHardForks
blk
where
- getEraParams :: TopLevelConfig blk -> EraParams
- toPartialLedgerConfig :: proxy blk -> LedgerConfig blk -> PartialLedgerConfig blk
- noHardForksEpochInfo :: ( Monad m, NoHardForks blk) => TopLevelConfig blk -> EpochInfo m
- class ( All SingleEraBlock xs, Typeable xs, IsNonEmpty xs) => CanHardFork xs where
- type HardForkLedgerView = HardForkLedgerView_ WrapLedgerView
-
data
HardForkLedgerView_
f xs =
HardForkLedgerView
{
- hardForkLedgerViewTransition :: ! TransitionInfo
- hardForkLedgerViewPerEra :: !( HardForkState f xs)
- newtype MismatchEraInfo xs = MismatchEraInfo { }
- newtype OneEraHash (xs :: [k]) = OneEraHash { }
-
newtype
OneEraTipInfo
xs =
OneEraTipInfo
{
- getOneEraTipInfo :: NS WrapTipInfo xs
-
newtype
OneEraHeader
xs =
OneEraHeader
{
- getOneEraHeader :: NS Header xs
-
newtype
OneEraGenTxId
xs =
OneEraGenTxId
{
- getOneEraGenTxId :: NS WrapGenTxId xs
-
newtype
OneEraGenTx
xs =
OneEraGenTx
{
- getOneEraGenTx :: NS GenTx xs
-
newtype
OneEraBlock
xs =
OneEraBlock
{
- getOneEraBlock :: NS I xs
- newtype OneEraApplyTxErr xs = OneEraApplyTxErr { }
- newtype PerEraStorageConfig xs = PerEraStorageConfig { }
- newtype PerEraLedgerConfig xs = PerEraLedgerConfig { }
- newtype PerEraConsensusConfig xs = PerEraConsensusConfig { }
- newtype PerEraCodecConfig xs = PerEraCodecConfig { }
- newtype PerEraBlockConfig xs = PerEraBlockConfig { }
-
data
HardForkLedgerConfig
xs =
HardForkLedgerConfig
{
- hardForkLedgerConfigShape :: !( Shape xs)
- hardForkLedgerConfigPerEra :: !( PerEraLedgerConfig xs)
-
newtype
HardForkBlock
xs =
HardForkBlock
{
- getHardForkBlock :: OneEraBlock xs
- data HardForkProtocol (xs :: [ Type ])
- completeLedgerConfig' :: forall blk. HasPartialLedgerConfig blk => EpochInfo ( Except PastHorizonException ) -> WrapPartialLedgerConfig blk -> LedgerConfig blk
- completeLedgerConfig'' :: forall blk. HasPartialLedgerConfig blk => EpochInfo ( Except PastHorizonException ) -> WrapPartialLedgerConfig blk -> WrapLedgerConfig blk
- completeConsensusConfig' :: forall blk. HasPartialConsensusConfig ( BlockProtocol blk) => EpochInfo ( Except PastHorizonException ) -> WrapPartialConsensusConfig blk -> ConsensusConfig ( BlockProtocol blk)
- completeConsensusConfig'' :: forall blk. HasPartialConsensusConfig ( BlockProtocol blk) => EpochInfo ( Except PastHorizonException ) -> WrapPartialConsensusConfig blk -> WrapConsensusConfig blk
- distribLedgerConfig :: CanHardFork xs => EpochInfo ( Except PastHorizonException ) -> LedgerConfig ( HardForkBlock xs) -> NP WrapLedgerConfig xs
- distribTopLevelConfig :: All SingleEraBlock xs => EpochInfo ( Except PastHorizonException ) -> TopLevelConfig ( HardForkBlock xs) -> NP TopLevelConfig xs
- distribAnnTip :: SListI xs => AnnTip ( HardForkBlock xs) -> NS AnnTip xs
- undistribAnnTip :: SListI xs => NS AnnTip xs -> AnnTip ( HardForkBlock xs)
- data HardForkValidationErr xs
- type HardForkCanBeLeader xs = SomeErasCanBeLeader xs
- type HardForkIsLeader xs = OneEraIsLeader xs
- type HardForkChainDepState xs = HardForkState WrapChainDepState xs
-
data
HardForkLedgerUpdate
xs
- = HardForkUpdateInEra ( OneEraLedgerUpdate xs)
- | HardForkUpdateTransitionConfirmed ( EraIndex xs) ( EraIndex xs) EpochNo
- | HardForkUpdateTransitionDone ( EraIndex xs) ( EraIndex xs) EpochNo
- | HardForkUpdateTransitionRolledBack ( EraIndex xs) ( EraIndex xs)
-
data
HardForkLedgerWarning
xs
- = HardForkWarningInEra ( OneEraLedgerWarning xs)
- | HardForkWarningTransitionMismatch ( EraIndex xs) EraParams EpochNo
- | HardForkWarningTransitionInFinalEra ( EraIndex xs) EpochNo
- | HardForkWarningTransitionUnconfirmed ( EraIndex xs)
- | HardForkWarningTransitionReconfirmed ( EraIndex xs) ( EraIndex xs) EpochNo EpochNo
-
data
AnnForecast
state view blk =
AnnForecast
{
- annForecast :: Forecast (view blk)
- annForecastState :: state blk
- annForecastTip :: WithOrigin SlotNo
- annForecastEnd :: Maybe Bound
- data HardForkEnvelopeErr xs
- data HardForkLedgerError xs
- mkHardForkForecast :: forall state view xs. SListI xs => InPairs ( TranslateForecast state view) xs -> HardForkState ( AnnForecast state view) xs -> Forecast ( HardForkLedgerView_ view xs)
-
data
HardForkApplyTxErr
xs
- = HardForkApplyTxErrFromEra !( OneEraApplyTxErr xs)
- | HardForkApplyTxErrWrongEra !( MismatchEraInfo xs)
- hardForkApplyTxErrToEither :: HardForkApplyTxErr xs -> Either ( MismatchEraInfo xs) ( OneEraApplyTxErr xs)
- hardForkApplyTxErrFromEither :: Either ( MismatchEraInfo xs) ( OneEraApplyTxErr xs) -> HardForkApplyTxErr xs
-
data
QueryHardFork
xs result
where
- GetInterpreter :: QueryHardFork xs ( Interpreter xs)
- GetCurrentEra :: QueryHardFork xs ( EraIndex xs)
-
data
QueryAnytime
result
where
- GetEraStart :: QueryAnytime ( Maybe Bound )
-
data
QueryIfCurrent
:: [
Type
] ->
Type
->
Type
where
- QZ :: BlockQuery x result -> QueryIfCurrent (x ': xs) result
- QS :: QueryIfCurrent xs result -> QueryIfCurrent (x ': xs) result
- type HardForkQueryResult xs = Either ( MismatchEraInfo xs)
- getHardForkQuery :: BlockQuery ( HardForkBlock xs) result -> ( forall result'. (result :~: HardForkQueryResult xs result') -> QueryIfCurrent xs result' -> r) -> ( forall x' xs'. (xs :~: (x' ': xs')) -> ProofNonEmpty xs' -> QueryAnytime result -> EraIndex xs -> r) -> ( forall x' xs'. (xs :~: (x' ': xs')) -> ProofNonEmpty xs' -> QueryHardFork xs result -> r) -> r
- encodeQueryAnytimeResult :: QueryAnytime result -> result -> Encoding
- decodeQueryAnytimeResult :: QueryAnytime result -> forall s. Decoder s result
- encodeQueryHardForkResult :: SListI xs => QueryHardFork xs result -> result -> Encoding
- decodeQueryHardForkResult :: SListI xs => QueryHardFork xs result -> forall s. Decoder s result
- hardForkQueryInfo :: All SingleEraBlock xs => QueryIfCurrent xs result -> NS SingleEraInfo xs
-
data
HardForkForgeStateInfo
xs
where
- CurrentEraLacksBlockForging :: EraIndex (x ': (y ': xs)) -> HardForkForgeStateInfo (x ': (y ': xs))
- CurrentEraForgeStateUpdated :: OneEraForgeStateInfo xs -> HardForkForgeStateInfo xs
- hardForkBlockForging :: forall m xs. ( CanHardFork xs, Monad m) => Text -> NonEmptyOptNP ( BlockForging m) xs -> BlockForging m ( HardForkBlock xs)
Documentation
data EpochInfo (m :: Type -> Type ) Source #
Information about epochs
Different epochs may have different sizes and different slot lengths. This
information is encapsulated by
EpochInfo
. It is parameterized over a monad
m
because the information about how long each epoch is may depend on
information derived from the blockchain itself. It ultimately requires acess
to state, and so either uses the monad for that or uses the monad to reify
failure due to cached state information being too stale for the current
query.
Constructors
EpochInfo | |
Fields
|
newtype LedgerEraInfo blk Source #
Additional newtype wrapper around
SingleEraInfo
This is primarily useful for use in error messages: it marks which era info came from the ledger, and which came from a tx block header/etc.
Constructors
LedgerEraInfo | |
Fields
|
Instances
Eq ( LedgerEraInfo blk) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Info Methods (==) :: LedgerEraInfo blk -> LedgerEraInfo blk -> Bool Source # (/=) :: LedgerEraInfo blk -> LedgerEraInfo blk -> Bool Source # |
|
Show ( LedgerEraInfo blk) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Info |
|
NoThunks ( LedgerEraInfo blk) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Info |
|
Serialise ( LedgerEraInfo blk) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Info Methods encode :: LedgerEraInfo blk -> Encoding Source # decode :: Decoder s ( LedgerEraInfo blk) Source # encodeList :: [ LedgerEraInfo blk] -> Encoding Source # decodeList :: Decoder s [ LedgerEraInfo blk] Source # |
data SingleEraInfo blk Source #
Information about an era (mostly for type errors)
Constructors
SingleEraInfo | |
Fields
|
Instances
data Product2 f g x y Source #
Constructors
Pair2 (f x y) (g x y) |
Instances
( Eq (f x y), Eq (g x y)) => Eq ( Product2 f g x y) Source # | |
( Show (f x y), Show (g x y)) => Show ( Product2 f g x y) Source # | |
Generic ( Product2 f g x y) Source # | |
type Rep ( Product2 f g x y) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Functors
type
Rep
(
Product2
f g x y) =
D1
('
MetaData
"Product2" "Ouroboros.Consensus.HardFork.Combinator.Util.Functors" "ouroboros-consensus-0.1.0.1-DT4Cvwf63DZKctsEvaJqCU" '
False
) (
C1
('
MetaCons
"Pair2" '
PrefixI
'
False
) (
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(f x y))
:*:
S1
('
MetaSel
('
Nothing
::
Maybe
Symbol
) '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(g x y))))
|
data family Ticked st :: Type Source #
" Ticked " piece of state (
LedgerState
,
LedgerView
,
ChainIndepState
)
Ticking refers to the passage of time (the ticking of the clock). When a piece of state is marked as ticked, it means that time-related changes have been applied to the state (or forecast).
Some examples of time related changes:
- Scheduled delegations might have been applied in Byron
- New leader schedule computed for Shelley
- Transition from Byron to Shelley activated in the hard fork combinator.
- Nonces switched out at the start of a new epoch.
Instances
data family NestedCtxt_ blk :: ( Type -> Type ) -> Type -> Type Source #
Context identifying what kind of block we have
In almost all places we will use
NestedCtxt
rather than
NestedCtxt_
.
Instances
data family Header blk :: Type Source #
Instances
data family StorageConfig blk :: Type Source #
Config needed for the
NodeInitStorage
class. Defined here to
avoid circular dependencies.
Instances
data family CodecConfig blk :: Type 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
data family BlockConfig blk :: Type Source #
Static configuration required to work with this type of blocks
Instances
Isomorphic BlockConfig Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project :: NoHardForks blk => BlockConfig ( HardForkBlock '[blk]) -> BlockConfig blk Source # inject :: NoHardForks blk => BlockConfig blk -> BlockConfig ( HardForkBlock '[blk]) Source # |
|
NoThunks ( BlockConfig ( DualBlock m a)) Source # | |
CanHardFork xs => NoThunks ( BlockConfig ( HardForkBlock xs)) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks :: Context -> BlockConfig ( HardForkBlock xs) -> IO ( Maybe ThunkInfo ) Source # wNoThunks :: Context -> BlockConfig ( HardForkBlock xs) -> IO ( Maybe ThunkInfo ) Source # showTypeOf :: Proxy ( BlockConfig ( HardForkBlock xs)) -> String Source # |
|
newtype BlockConfig ( HardForkBlock xs) Source # | |
|
|
data BlockConfig ( DualBlock m a) Source # | |
Defined in Ouroboros.Consensus.Ledger.Dual |
data family ConsensusConfig p :: Type 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
data family LedgerState blk :: Type Source #
Ledger state associated with a block
Instances
data family Validated x :: Type Source #
" Validated " transaction or block
The ledger defines how to validate transactions and blocks. It's possible the type before and after validation may be distinct (eg Alonzo transactions), which originally motivated this family.
We also gain the related benefit that certain interface functions, such as those that reapply blocks, can have a more precise type now. TODO
Similarly, the Node-to-Client mini protocols can explicitly indicate that the
client trusts the blocks from the local server, by having the server send
Validated
blocks to the client. TODO
Note that validation has different implications for a transaction than for a block. In particular, a validated transaction can be " reapplied " to different ledger states, whereas a validated block must only be " reapplied " to the exact same ledger state (eg as part of rebuilding from an on-disk ledger snapshot).
Since the ledger defines validation, see the ledger details for concrete
examples of what determines the validity (wrt to a
LedgerState
) of a
transaction and/or block. Example properties include: a transaction's claimed
inputs exist and are still unspent, a block carries a sufficient
cryptographic signature, etc.
Instances
data family TxId tx :: Type Source #
A generalized transaction,
GenTx
, identifier.
Instances
data family GenTx blk :: Type 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.