Skip to content

Commit

Permalink
Merge branch 'main' into dnadales/seed-a-glossary
Browse files Browse the repository at this point in the history
  • Loading branch information
dnadales authored Oct 18, 2023
2 parents 5d77967 + 51da387 commit d83aece
Show file tree
Hide file tree
Showing 50 changed files with 312 additions and 316 deletions.
2 changes: 1 addition & 1 deletion docs/website/contents/for-developers/AbstractProtocol.md
Original file line number Diff line number Diff line change
Expand Up @@ -201,7 +201,7 @@ Classes connected to ledgers:

-- | Link protocol to ledger
class (BlockSupportsProtocol b, UpdateLedger b, ValidateEnvelope b) => LedgerSupportsProtocol b where
protocolLedgerView :: lc Ticked l Ticked ledvw -- 'ledvw' ('LedgerView (BlockProtocol b)') extracted from the ledger
protocolLedgerView :: lc Ticked l ledvw -- 'ledvw' ('LedgerView (BlockProtocol b)') extracted from the ledger
ledgerViewForecastAt :: lc l Forecast ledvw -- get a forecast (of future 'ledvw's) from a given ledger state.

class (UpdateLedger b) => LedgerSupportsMempool b where
Expand Down
14 changes: 6 additions & 8 deletions docs/website/contents/for-developers/HardWonWisdom.md
Original file line number Diff line number Diff line change
Expand Up @@ -44,9 +44,7 @@ instance ... => LedgerSupportsProtocol (ShelleyBlock (TPraos crypto) era) where
ledgerViewForecastAt cfg ledgerState = Forecast at $ \for ->
if
| NotOrigin for == at ->
return
$ TPraos.TickedPraosLedgerView
$ SL.currentLedgerView shelleyLedgerState
return $ SL.currentLedgerView shelleyLedgerState
| for < maxFor -> return $ futureLedgerView for
| otherwise -> throwError OutsideForecastRange { ... }
where
Expand All @@ -56,11 +54,11 @@ instance ... => LedgerSupportsProtocol (ShelleyBlock (TPraos crypto) era) where
swindow = SL.stabilityWindow globals
at = ledgerTipSlot ledgerState

futureLedgerView :: SlotNo -> Ticked (SL.LedgerView (EraCrypto era))
futureLedgerView :: SlotNo -> SL.LedgerView (EraCrypto era)
futureLedgerView =
either
(\e -> error ("futureLedgerView failed: " <> show e))
TPraos.TickedPraosLedgerView
id
. SL.futureLedgerView globals shelleyLedgerState

maxFor :: SlotNo -- Exclusive upper bound
Expand Down Expand Up @@ -115,13 +113,13 @@ Thus using HCG window as Stability Window ensures that forecasting can't disrupt

## How does cross-era forecasting work?

When we talk about forecasting, we mean about the process of trying to get a ticked ledger view from a ledger state for a given slot. This ledger view can then be used to verify the validity of headers in that slot that live on the same chain as the original ledger state.
When we talk about forecasting, we mean about the process of trying to get a ledger view from a ledger state for a given slot. This ledger view can then be used to verify the validity of headers in that slot that live on the same chain as the original ledger state.

Hence, in the context of the HFC which has to support forecasts across era boundaries, forecasting can be thought of to have type
```haskell
SlotNo
-> LedgerState blk
-> Either OutsideForecastRange (Ticked (LedgerView (BlockProtocol blk')))
-> Either OutsideForecastRange (LedgerView (BlockProtocol blk'))
```
(in reality, there is an intermediate `Forecast` type, see `ledgerViewForecastAt`).

Expand All @@ -148,7 +146,7 @@ Hence, the HFC fully offloads the task to work out a safe way to do cross-era fo
In our case, there are two cases of era transitions:

- **Intra-Shelley:** These are trivial to support, as there are almost no changes regarding forecasting, so we can simply forecast starting in the old era and then convert the resulting `LedgerView` to the new era.
- The `LedgerView` actually only depends on the `ConsensusProtocol`, which only changed from Alonzo/TPraos to Babbage/Praos (Vasil HF), and even there, the translation only consists of un- and rewrapping (see `translateTickedLedgerView`).
- The `LedgerView` actually only depends on the `ConsensusProtocol`, which only changed from Alonzo/TPraos to Babbage/Praos (Vasil HF), and even there, the translation only consists of un- and rewrapping (see `translateLedgerView`).
- The stability window/forecasting range also stayed the same so far, but there already is existing logic to handle changes there, see the usage of the very conservative `crossEraForecastBound` in `forecastAcrossShelley`. (We definitely will want to revisit that in case we actually ever do a change here.)

- **Byron-to-Shelley:** This is implemented in `crossEraForecastByronToShelleyWrapper`, and exploits the fact that the ledger view for the first Shelley epoch is independent of the Byron ledger state, and can be constructed just using the static Shelley ledger config.
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
<!--
A new scriv changelog fragment.
Uncomment the section that is right (remove the HTML comment wrapper).
-->

<!--
### Patch
- A bullet item for the Patch category.
-->
<!--
### Non-Breaking
- A bullet item for the Non-Breaking category.
-->
### Breaking

- Remove `Ticked (LedgerView X)` data family instances.
- Remove `toTickedPBftLedgerView`.
Original file line number Diff line number Diff line change
Expand Up @@ -230,7 +230,7 @@ getProtocolParameters =

instance LedgerSupportsProtocol ByronBlock where
protocolLedgerView _cfg =
toTickedPBftLedgerView
toPBftLedgerView
. CC.getDelegationMap
. tickedByronLedgerState

Expand All @@ -250,7 +250,7 @@ instance LedgerSupportsProtocol ByronBlock where
-- To create a forecast, take the delegation state from the given ledger
-- state, and apply the updates that should be applied by the given slot.
ledgerViewForecastAt cfg (ByronLedgerState _tipBlkNo st _) = Forecast at $ \for ->
toTickedPBftLedgerView <$> if
toPBftLedgerView <$> if
| for == lastSlot ->
return $ CC.getDelegationMap st
| for < maxFor ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@ module Ouroboros.Consensus.Byron.Ledger.PBFT (
, fromPBftLedgerView
, mkByronContextDSIGN
, toPBftLedgerView
, toTickedPBftLedgerView
) where

import qualified Cardano.Chain.Block as CC
Expand Down Expand Up @@ -75,9 +74,6 @@ instance BlockSupportsProtocol ByronBlock where
toPBftLedgerView :: Delegation.Map -> PBftLedgerView PBftByronCrypto
toPBftLedgerView = PBftLedgerView . Delegation.unMap

toTickedPBftLedgerView :: Delegation.Map -> Ticked (PBftLedgerView PBftByronCrypto)
toTickedPBftLedgerView = TickedPBftLedgerView . Delegation.unMap

fromPBftLedgerView :: PBftLedgerView PBftByronCrypto -> Delegation.Map
fromPBftLedgerView = Delegation.Map . pbftDelegates

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -482,11 +482,11 @@ crossEraForecastByronToShelleyWrapper =
-> LedgerState ByronBlock
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
(WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
forecast cfgShelley bound forecastFor currentByronState
| forecastFor < maxFor
= return $
WrapTickedLedgerView $ TickedPraosLedgerView $
WrapLedgerView $
SL.mkInitialShelleyLedgerView
(toFromByronTranslationContext (shelleyLedgerGenesis cfgShelley))
| otherwise
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -84,8 +84,7 @@ import Ouroboros.Consensus.Ledger.Abstract
import Ouroboros.Consensus.Ledger.CommonProtocolParams
import Ouroboros.Consensus.Ledger.Extended
import Ouroboros.Consensus.Protocol.Ledger.Util (isNewEpoch)
import Ouroboros.Consensus.Protocol.TPraos (MaxMajorProtVer (..),
Ticked (TickedPraosLedgerView))
import Ouroboros.Consensus.Protocol.TPraos (MaxMajorProtVer (..))
import Ouroboros.Consensus.Shelley.Eras (EraCrypto)
import Ouroboros.Consensus.Shelley.Ledger.Block
import Ouroboros.Consensus.Shelley.Ledger.Config
Expand Down Expand Up @@ -474,8 +473,8 @@ instance ShelleyCompatible proto era => ValidateEnvelope (ShelleyBlock proto era
type OtherHeaderEnvelopeError (ShelleyBlock proto era) =
EnvelopeCheckError proto

additionalEnvelopeChecks cfg tlv hdr =
envelopeChecks (configConsensus cfg) tlv (shelleyHeaderRaw hdr)
additionalEnvelopeChecks cfg lv hdr =
envelopeChecks (configConsensus cfg) lv (shelleyHeaderRaw hdr)

{-------------------------------------------------------------------------------
Auxiliary
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -35,12 +35,10 @@ import Ouroboros.Consensus.Ledger.Abstract
import Ouroboros.Consensus.Ledger.SupportsProtocol
(LedgerSupportsProtocol (..))
import Ouroboros.Consensus.Protocol.Praos (Praos)
import qualified Ouroboros.Consensus.Protocol.Praos as Praos
import qualified Ouroboros.Consensus.Protocol.Praos.Views as Praos
import Ouroboros.Consensus.Protocol.TPraos (TPraos)
import qualified Ouroboros.Consensus.Protocol.TPraos as TPraos
import Ouroboros.Consensus.Protocol.Translate (TranslateProto,
translateTickedLedgerView)
translateLedgerView)
import Ouroboros.Consensus.Shelley.Eras (EraCrypto)
import Ouroboros.Consensus.Shelley.Ledger.Block
import Ouroboros.Consensus.Shelley.Ledger.Ledger
Expand All @@ -53,17 +51,14 @@ instance
(ShelleyCompatible (TPraos crypto) era, crypto ~ EraCrypto era) =>
LedgerSupportsProtocol (ShelleyBlock (TPraos crypto) era)
where
protocolLedgerView _cfg =
TPraos.TickedPraosLedgerView
. SL.currentLedgerView
. tickedShelleyLedgerState
protocolLedgerView _cfg = SL.currentLedgerView . tickedShelleyLedgerState

-- Extra context available in
-- https://github.com/input-output-hk/ouroboros-network/blob/master/ouroboros-consensus/docs/HardWonWisdom.md#why-doesnt-ledger-code-ever-return-pasthorizonexception
ledgerViewForecastAt cfg ledgerState = Forecast at $ \for ->
if
| NotOrigin for == at ->
return $ TPraos.TickedPraosLedgerView $ SL.currentLedgerView shelleyLedgerState
return $ SL.currentLedgerView shelleyLedgerState
| for < maxFor ->
return $ futureLedgerView for
| otherwise ->
Expand All @@ -79,11 +74,11 @@ instance
swindow = SL.stabilityWindow globals
at = ledgerTipSlot ledgerState

futureLedgerView :: SlotNo -> Ticked (SL.LedgerView (EraCrypto era))
futureLedgerView :: SlotNo -> SL.LedgerView (EraCrypto era)
futureLedgerView =
either
(\e -> error ("futureLedgerView failed: " <> show e))
TPraos.TickedPraosLedgerView
id
. SL.futureLedgerView globals shelleyLedgerState

-- Exclusive upper bound
Expand All @@ -106,20 +101,19 @@ instance
pparam :: forall a. Lens.Micro.Lens' (LedgerCore.PParams era) a -> a
pparam lens = getPParams nes Lens.Micro.^. lens

in Praos.TickedPraosLedgerView $
Praos.LedgerView
{ Praos.lvPoolDistr = nesPd,
Praos.lvMaxBodySize = pparam LedgerCore.ppMaxBBSizeL,
Praos.lvMaxHeaderSize = pparam LedgerCore.ppMaxBHSizeL,
Praos.lvProtocolVersion = pparam LedgerCore.ppProtocolVersionL
}
in Praos.LedgerView
{ Praos.lvPoolDistr = nesPd,
Praos.lvMaxBodySize = pparam LedgerCore.ppMaxBBSizeL,
Praos.lvMaxHeaderSize = pparam LedgerCore.ppMaxBHSizeL,
Praos.lvProtocolVersion = pparam LedgerCore.ppProtocolVersionL
}

-- | Currently the Shelley+ ledger is hard-coded to produce a TPraos ledger
-- view. Since we can convert them, we piggy-back on this to get a Praos
-- ledger view. Ultimately, we will want to liberalise the ledger code
-- slightly.
ledgerViewForecastAt cfg st =
mapForecast (translateTickedLedgerView @(TPraos crypto) @(Praos crypto)) $
mapForecast (translateLedgerView @(TPraos crypto) @(Praos crypto)) $
ledgerViewForecastAt @(ShelleyBlock (TPraos crypto) era) cfg st'
where
st' :: LedgerState (ShelleyBlock (TPraos crypto) era)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,6 @@ import Ouroboros.Consensus.Protocol.Abstract (CanBeLeader,
IsLeader, LedgerView, ValidateView)
import Ouroboros.Consensus.Protocol.Ledger.HotKey (HotKey)
import Ouroboros.Consensus.Protocol.Signed (SignedHeader)
import Ouroboros.Consensus.Ticked (Ticked)
import Ouroboros.Consensus.Util.Condense (Condense (..))

{-------------------------------------------------------------------------------
Expand Down Expand Up @@ -118,7 +117,7 @@ class
-- check things like maximum header size.
envelopeChecks ::
ConsensusConfig proto ->
Ticked (LedgerView proto) ->
LedgerView proto ->
ShelleyProtocolHeader proto ->
Except (EnvelopeCheckError proto) ()

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,7 @@ instance PraosCrypto c => ProtocolHeaderSupportsEnvelope (Praos c) where

type EnvelopeCheckError _ = PraosEnvelopeError

envelopeChecks cfg (TickedPraosLedgerView lv) hdr = do
envelopeChecks cfg lv hdr = do
unless (m <= maxpv) $ throwError (ObsoleteNode m maxpv)
unless (fromIntegral (bhviewHSize bhv) <= maxHeaderSize) $
throwError $
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,8 @@ import Ouroboros.Consensus.Protocol.Signed (Signed,
import Ouroboros.Consensus.Protocol.TPraos
(MaxMajorProtVer (MaxMajorProtVer), TPraos,
TPraosCannotForge, TPraosFields (..), TPraosToSign (..),
Ticked (TickedPraosLedgerView), forgeTPraosFields,
tpraosMaxMajorPV, tpraosParams, tpraosSlotsPerKESPeriod)
forgeTPraosFields, tpraosMaxMajorPV, tpraosParams,
tpraosSlotsPerKESPeriod)
import Ouroboros.Consensus.Shelley.Protocol.Abstract (ProtoCrypto,
ProtocolHeaderSupportsEnvelope (..),
ProtocolHeaderSupportsKES (..),
Expand All @@ -46,7 +46,7 @@ instance PraosCrypto c => ProtocolHeaderSupportsEnvelope (TPraos c) where

type EnvelopeCheckError _ = ChainPredicateFailure

envelopeChecks cfg (TickedPraosLedgerView lv) hdr =
envelopeChecks cfg lv hdr =
SL.chainChecks
maxPV
(SL.lvChainChecks lv)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -250,7 +250,7 @@ forecastAcrossShelley ::
-> Bound -- ^ Transition between the two eras
-> SlotNo -- ^ Forecast for this slot
-> LedgerState (ShelleyBlock protoFrom eraFrom)
-> Except OutsideForecastRange (Ticked (WrapLedgerView (ShelleyBlock protoTo eraTo)))
-> Except OutsideForecastRange (WrapLedgerView (ShelleyBlock protoTo eraTo))
forecastAcrossShelley cfgFrom cfgTo transition forecastFor ledgerStateFrom
| forecastFor < maxFor
= return $ futureLedgerView forecastFor
Expand All @@ -263,12 +263,12 @@ forecastAcrossShelley cfgFrom cfgTo transition forecastFor ledgerStateFrom
where
-- | 'SL.futureLedgerView' imposes its own bounds. Those bounds could
-- /exceed/ the 'maxFor' we have computed, but should never be /less/.
futureLedgerView :: SlotNo -> Ticked (WrapLedgerView (ShelleyBlock protoTo era))
futureLedgerView :: SlotNo -> WrapLedgerView (ShelleyBlock protoTo era)
futureLedgerView =
WrapTickedLedgerView
WrapLedgerView
. either
(\e -> error ("futureLedgerView failed: " <> show e))
(Proto.translateTickedLedgerView @protoFrom @protoTo)
(Proto.translateLedgerView @protoFrom @protoTo)
. runExcept
. Forecast.forecastFor (ledgerViewForecastAt cfgFrom ledgerStateFrom)

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -524,11 +524,11 @@ benchmarkLedgerOps mOutfile AnalysisEnv {db, registry, initLedger, cfg, limit} =
let slot = blockSlot blk
-- We do not use strictness annotation on the resulting tuples since
-- 'time' takes care of forcing the evaluation of its argument's result.
(tkLdgrView, tForecast) <- time $ forecast slot prevLedgerState
(tkHdrSt, tHdrTick) <- time $ tickTheHeaderState slot prevLedgerState tkLdgrView
(hdrSt', tHdrApp) <- time $ applyTheHeader tkLdgrView tkHdrSt
(tkLdgrSt, tBlkTick) <- time $ tickTheLedgerState slot prevLedgerState
(ldgrSt', tBlkApp) <- time $ applyTheBlock tkLdgrSt
(ldgrView, tForecast) <- time $ forecast slot prevLedgerState
(tkHdrSt, tHdrTick) <- time $ tickTheHeaderState slot prevLedgerState ldgrView
(hdrSt', tHdrApp) <- time $ applyTheHeader ldgrView tkHdrSt
(tkLdgrSt, tBlkTick) <- time $ tickTheLedgerState slot prevLedgerState
(ldgrSt', tBlkApp) <- time $ applyTheBlock tkLdgrSt

currentRtsStats <- GC.getRTSStats
let
Expand Down Expand Up @@ -565,7 +565,7 @@ benchmarkLedgerOps mOutfile AnalysisEnv {db, registry, initLedger, cfg, limit} =
forecast ::
SlotNo
-> ExtLedgerState blk
-> IO (Ticked (LedgerView (BlockProtocol blk)))
-> IO (LedgerView (BlockProtocol blk))
forecast slot st = do
let forecaster = ledgerViewForecastAt lcfg (ledgerState st)
case runExcept $ forecastFor forecaster slot of
Expand All @@ -575,20 +575,20 @@ benchmarkLedgerOps mOutfile AnalysisEnv {db, registry, initLedger, cfg, limit} =
tickTheHeaderState ::
SlotNo
-> ExtLedgerState blk
-> Ticked (LedgerView (BlockProtocol blk))
-> LedgerView (BlockProtocol blk)
-> IO (Ticked (HeaderState blk))
tickTheHeaderState slot st tickedLedgerView =
tickTheHeaderState slot st ledgerView =
pure $! tickHeaderState ccfg
tickedLedgerView
ledgerView
slot
(headerState st)

applyTheHeader ::
Ticked (LedgerView (BlockProtocol blk))
LedgerView (BlockProtocol blk)
-> Ticked (HeaderState blk)
-> IO (HeaderState blk)
applyTheHeader tickedLedgerView tickedHeaderState = do
case runExcept $ validateHeader cfg tickedLedgerView (getHeader blk) tickedHeaderState of
applyTheHeader ledgerView tickedHeaderState = do
case runExcept $ validateHeader cfg ledgerView (getHeader blk) tickedHeaderState of
Left err -> fail $ "benchmark doesn't support invalid headers: " <> show rp <> " " <> show err
Right x -> pure x

Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
<!--
A new scriv changelog fragment.
Uncomment the section that is right (remove the HTML comment wrapper).
-->

### Patch

- In tests only: replace all occurrences of `WrapTickedLedgerView` and `TickedTrivial` with `WrapLedgerView` and `()`.

<!--
### Non-Breaking
- A bullet item for the Non-Breaking category.
-->
<!--
### Breaking
- A bullet item for the Breaking category.
-->
Original file line number Diff line number Diff line change
Expand Up @@ -310,7 +310,7 @@ forkBlockForging IS{..} blockForging =

trace $ TraceLedgerState currentSlot bcPrevPoint

-- We require the ticked ledger view in order to construct the ticked
-- We require the ledger view in order to construct the ticked
-- 'ChainDepState'.
ledgerView <-
case runExcept $ forecastFor
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -429,7 +429,7 @@ forecast_AtoB ::
BlockA
BlockB
forecast_AtoB = InPairs.ignoringBoth $ CrossEraForecaster $ \_ _ _ -> return $
WrapTickedLedgerView TickedTrivial
WrapLedgerView ()

injectTx_AtoB ::
RequiringBoth
Expand Down
Loading

0 comments on commit d83aece

Please sign in to comment.