Skip to content

Commit c4855c3

Browse files
committed
WIP HFC: translate between Peras rounds and slots
1 parent 2a78ec8 commit c4855c3

File tree

6 files changed

+147
-7
lines changed

6 files changed

+147
-7
lines changed

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Block/SupportsPeras.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,10 +21,12 @@ import Data.Word (Word64)
2121
import GHC.Generics (Generic)
2222
import NoThunks.Class
2323
import Ouroboros.Consensus.Block.Abstract
24+
import Codec.Serialise.Class
2425

2526
newtype PerasRoundNo = PerasRoundNo {unPerasRoundNo :: Word64}
26-
deriving stock (Show, Generic)
27-
deriving newtype (Eq, Ord, NoThunks)
27+
deriving stock Show
28+
deriving Generic
29+
deriving newtype (Eq, Ord, NoThunks, Serialise)
2830

2931
newtype PerasWeight = PerasWeight {unPerasWeight :: Word64}
3032
deriving stock (Show, Generic)

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/History/Qry.hs

Lines changed: 69 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,8 @@ module Ouroboros.Consensus.HardFork.History.Qry
4242
, slotToSlotLength
4343
, slotToWallclock
4444
, wallclockToSlot
45+
, perasRoundNoToSlot
46+
, slotToPerasRoundNo
4547
) where
4648

4749
import Codec.Serialise (Serialise (..))
@@ -126,6 +128,8 @@ import Quiet
126128
127129
These are equal by (INV-2a).
128130
131+
5. Slot to Peras round translation.
132+
129133
This means that for values at that boundary, it does not matter if we use
130134
this era or the next era for the translation. However, this is only true for
131135
these 4 translations. If we are returning the era parameters directly, then
@@ -182,12 +186,14 @@ newtype TimeInSlot = TimeInSlot {getTimeInSlot :: NominalDiffTime} deriving Gene
182186
newtype SlotInEra = SlotInEra {getSlotInEra :: Word64} deriving Generic
183187
newtype SlotInEpoch = SlotInEpoch {getSlotInEpoch :: Word64} deriving Generic
184188
newtype EpochInEra = EpochInEra {getEpochInEra :: Word64} deriving Generic
189+
newtype PerasRoundNoInEra = PerasRoundNoInEra {getPerasRoundNoInEra :: Word64} deriving Generic
185190

186191
deriving via Quiet TimeInEra instance Show TimeInEra
187192
deriving via Quiet TimeInSlot instance Show TimeInSlot
188193
deriving via Quiet SlotInEra instance Show SlotInEra
189194
deriving via Quiet SlotInEpoch instance Show SlotInEpoch
190195
deriving via Quiet EpochInEra instance Show EpochInEra
196+
deriving via Quiet PerasRoundNoInEra instance Show PerasRoundNoInEra
191197

192198
{-------------------------------------------------------------------------------
193199
Expressions
@@ -212,23 +218,28 @@ data Expr (f :: Type -> Type) :: Type -> Type where
212218
EAbsToRelTime :: Expr f RelativeTime -> Expr f TimeInEra
213219
EAbsToRelSlot :: Expr f SlotNo -> Expr f SlotInEra
214220
EAbsToRelEpoch :: Expr f EpochNo -> Expr f EpochInEra
221+
EAbsToRelPerasRoundNo :: Expr f PerasRoundNo -> Expr f PerasRoundNoInEra
215222
-- Convert from era-relative to absolute
216223

217224
ERelToAbsTime :: Expr f TimeInEra -> Expr f RelativeTime
218225
ERelToAbsSlot :: Expr f (SlotInEra, TimeInSlot) -> Expr f SlotNo
219226
ERelToAbsEpoch :: Expr f (EpochInEra, SlotInEpoch) -> Expr f EpochNo
227+
ERelToAbsPerasRoundNo :: Expr f PerasRoundNoInEra -> Expr f PerasRoundNo
220228
-- Convert between relative values
221229

222230
ERelTimeToSlot :: Expr f TimeInEra -> Expr f (SlotInEra, TimeInSlot)
223231
ERelSlotToTime :: Expr f SlotInEra -> Expr f TimeInEra
224232
ERelSlotToEpoch :: Expr f SlotInEra -> Expr f (EpochInEra, SlotInEpoch)
225233
ERelEpochToSlot :: Expr f EpochInEra -> Expr f SlotInEra
234+
ERelPerasRoundNoToSlot :: Expr f PerasRoundNoInEra -> Expr f SlotInEra
235+
ERelSlotToPerasRoundNo :: Expr f SlotInEra -> Expr f PerasRoundNoInEra
226236
-- Get era parameters
227237

228238
-- The arguments are used for bound checks
229239
ESlotLength :: Expr f SlotNo -> Expr f SlotLength
230240
EEpochSize :: Expr f EpochNo -> Expr f EpochSize
231241
EGenesisWindow :: Expr f SlotNo -> Expr f GenesisWindow
242+
EPerasRoundLength :: Expr f SlotNo -> Expr f PerasRoundLength
232243

233244
{-------------------------------------------------------------------------------
234245
Interpreter
@@ -279,6 +290,11 @@ evalExprInEra EraSummary{..} = \(ClosedExpr e) -> go e
279290
e <- go expr
280291
guard (e >= boundEpoch eraStart)
281292
return $ EpochInEra (countEpochs e (boundEpoch eraStart))
293+
go (EAbsToRelPerasRoundNo expr) = do
294+
absPerasRoundNo <- go expr
295+
guard $ absPerasRoundNo >= boundPerasRound eraStart
296+
-- TODO(geo2a): check we are in Peras-enabled era
297+
pure $ PerasRoundNoInEra (countPerasRounds absPerasRoundNo (boundPerasRound eraStart))
282298

283299
-- Convert relative to absolute
284300
--
@@ -304,6 +320,12 @@ evalExprInEra EraSummary{..} = \(ClosedExpr e) -> go e
304320
absEpoch < boundEpoch end
305321
|| absEpoch == boundEpoch end && getSlotInEpoch s == 0
306322
return absEpoch
323+
go (ERelToAbsPerasRoundNo expr) = do
324+
relPerasRound <- go expr
325+
let absPerasRound = addPerasRounds (getPerasRoundNoInEra relPerasRound) (boundPerasRound eraStart)
326+
guardEnd $ \end -> absPerasRound <= boundPerasRound end
327+
-- TODO(geo2a): how to check that we are in Peras-enabled era?
328+
pure absPerasRound
307329

308330
-- Convert between relative values
309331
--
@@ -321,7 +343,15 @@ evalExprInEra EraSummary{..} = \(ClosedExpr e) -> go e
321343
go (ERelEpochToSlot expr) = do
322344
e <- go expr
323345
return $ SlotInEra (getEpochInEra e * epochSize)
324-
346+
go (ERelPerasRoundNoToSlot expr) = do
347+
r <- go expr
348+
let slot = getPerasRoundNoInEra r * unPerasRoundLength eraPerasRoundLength
349+
pure (SlotInEra slot)
350+
go (ERelSlotToPerasRoundNo expr) = do
351+
s <- go expr
352+
let perasRoundNo = getSlotInEra s `div` unPerasRoundLength eraPerasRoundLength
353+
guardEnd $ \end -> perasRoundNo < unPerasRoundNo (boundPerasRound end)
354+
pure (PerasRoundNoInEra perasRoundNo)
325355
-- Get era parameters
326356
--
327357
-- Here the upper bound must definitely be exclusive, or we'd return the
@@ -342,6 +372,14 @@ evalExprInEra EraSummary{..} = \(ClosedExpr e) -> go e
342372
guard $ s >= boundSlot eraStart
343373
guardEnd $ \end -> s < boundSlot end
344374
return eraGenesisWin
375+
go (EPerasRoundLength expr) = do
376+
s <- go expr
377+
guard $ s >= boundSlot eraStart
378+
guardEnd $ \end -> s < boundSlot end
379+
-- TODO(geo2a): do we need to check that round length divides epoch length here?
380+
((_, _), es) <- go $ slotToEpochExpr s
381+
guard $ (unEpochSize es) `mod` (unPerasRoundLength eraPerasRoundLength) == 0
382+
return eraPerasRoundLength
345383

346384
{-------------------------------------------------------------------------------
347385
PastHorizonException
@@ -382,7 +420,9 @@ instance Exception PastHorizonException
382420
runQuery ::
383421
forall a xs.
384422
HasCallStack =>
385-
Qry a -> Summary xs -> Either PastHorizonException a
423+
Qry a ->
424+
Summary xs ->
425+
Either PastHorizonException a
386426
runQuery qry (Summary summary) = go summary
387427
where
388428
go :: NonEmpty xs' EraSummary -> Either PastHorizonException a
@@ -528,6 +568,17 @@ epochToSize :: EpochNo -> Qry EpochSize
528568
epochToSize absEpoch =
529569
qryFromExpr (epochToSizeExpr absEpoch)
530570

571+
-- | Translate 'PerasRoundNo' to the 'SlotNo' of the first slot in that Peras round
572+
--
573+
-- Additionally returns the length of the round.
574+
-- perasRoundNoToSlot :: PerasRoundNo -> Qry (SlotNo, PerasRoundLength)
575+
perasRoundNoToSlot :: PerasRoundNo -> Qry SlotNo
576+
perasRoundNoToSlot perasRoundNo = qryFromExpr (perasRoundNoToSlotExpr perasRoundNo)
577+
578+
-- | Translate 'SlotNo' to its corresponding 'PerasRoundNo'
579+
slotToPerasRoundNo :: SlotNo -> Qry PerasRoundNo
580+
slotToPerasRoundNo absSlot = qryFromExpr (slotToPerasRoundNoExpr absSlot)
581+
531582
{-------------------------------------------------------------------------------
532583
Supporting expressions for the queries above
533584
-------------------------------------------------------------------------------}
@@ -581,6 +632,17 @@ slotToGenesisWindow :: SlotNo -> Expr f GenesisWindow
581632
slotToGenesisWindow absSlot =
582633
EGenesisWindow (ELit absSlot)
583634

635+
perasRoundNoToSlotExpr :: PerasRoundNo -> Expr f SlotNo
636+
perasRoundNoToSlotExpr absPerasRoundNo =
637+
let relPerasRoundExpr = EAbsToRelPerasRoundNo (ELit absPerasRoundNo)
638+
startOfSlot = ELit (TimeInSlot 0)
639+
in ERelToAbsSlot (EPair (ERelPerasRoundNoToSlot relPerasRoundExpr) startOfSlot)
640+
641+
-- SlotNo -> SlotInEra -> PerasRoundNoInEra -> PerasRoundNo
642+
643+
slotToPerasRoundNoExpr :: SlotNo -> Expr f PerasRoundNo
644+
slotToPerasRoundNoExpr absSlot = ERelToAbsPerasRoundNo (ERelSlotToPerasRoundNo (EAbsToRelSlot (ELit absSlot)))
645+
584646
{-------------------------------------------------------------------------------
585647
'Show' instances
586648
-------------------------------------------------------------------------------}
@@ -629,13 +691,18 @@ instance Show (ClosedExpr a) where
629691
EAbsToRelTime e -> showString "EAbsToRelTime " . go n 11 e
630692
EAbsToRelSlot e -> showString "EAbsToRelSlot " . go n 11 e
631693
EAbsToRelEpoch e -> showString "EAbsToRelEpoch " . go n 11 e
694+
EAbsToRelPerasRoundNo e -> showString "EAbsToRelPerasRoundNo " . go n 11 e
632695
ERelToAbsTime e -> showString "ERelToAbsTime " . go n 11 e
633696
ERelToAbsSlot e -> showString "ERelToAbsSlot " . go n 11 e
634697
ERelToAbsEpoch e -> showString "ERelToAbsEpoch " . go n 11 e
698+
ERelToAbsPerasRoundNo e -> showString "ERelToAbsPerasRoundNo " . go n 11 e
635699
ERelTimeToSlot e -> showString "ERelTimeToSlot " . go n 11 e
636700
ERelSlotToTime e -> showString "ERelSlotToTime " . go n 11 e
637701
ERelSlotToEpoch e -> showString "ERelSlotToEpoch " . go n 11 e
638702
ERelEpochToSlot e -> showString "ERelEpochToSlot " . go n 11 e
703+
ERelPerasRoundNoToSlot e -> showString "ERelPerasRoundNoToSlot " . go n 11 e
704+
ERelSlotToPerasRoundNo e -> showString "ERelSlotToPerasRoundNo " . go n 11 e
639705
ESlotLength e -> showString "ESlotLength " . go n 11 e
640706
EEpochSize e -> showString "EEpochSize " . go n 11 e
641707
EGenesisWindow e -> showString "EGenesisWindow " . go n 11 e
708+
EPerasRoundLength e -> showString "EPerasRoundLength " . go n 11 e

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/History/Summary.hs

Lines changed: 25 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -83,6 +83,7 @@ data Bound = Bound
8383
{ boundTime :: !RelativeTime
8484
, boundSlot :: !SlotNo
8585
, boundEpoch :: !EpochNo
86+
, boundPerasRound :: !PerasRoundNo
8687
}
8788
deriving stock (Show, Eq, Generic)
8889
deriving anyclass NoThunks
@@ -93,6 +94,7 @@ initBound =
9394
{ boundTime = RelativeTime 0
9495
, boundSlot = SlotNo 0
9596
, boundEpoch = EpochNo 0
97+
, boundPerasRound = PerasRoundNo 0
9698
}
9799

98100
-- | Version of 'mkUpperBound' when the upper bound may not be known
@@ -122,11 +124,14 @@ mkUpperBound EraParams{..} lo hiEpoch =
122124
{ boundTime = addRelTime inEraTime $ boundTime lo
123125
, boundSlot = addSlots inEraSlots $ boundSlot lo
124126
, boundEpoch = hiEpoch
127+
, boundPerasRound = addPerasRounds inEraPerasRounds $ boundPerasRound lo
125128
}
126129
where
127-
inEraEpochs, inEraSlots :: Word64
130+
inEraEpochs, inEraSlots, inEraPerasRounds :: Word64
128131
inEraEpochs = countEpochs hiEpoch (boundEpoch lo)
129132
inEraSlots = inEraEpochs * unEpochSize eraEpochSize
133+
-- TODO(geo2a): the bound on Peras rounds may need to be
134+
inEraPerasRounds = inEraSlots `div` (unPerasRoundLength eraPerasRoundLength)
130135

131136
inEraTime :: NominalDiffTime
132137
inEraTime = fromIntegral inEraSlots * getSlotLength eraSlotLength
@@ -182,6 +187,10 @@ slotToEpochBound EraParams{eraEpochSize = EpochSize epochSize} lo hiSlot =
182187
-- > t' - t == ((s' - s) * slotLen)
183188
-- > (t' - t) / slotLen == s' - s
184189
-- > s + ((t' - t) / slotLen) == s'
190+
--
191+
-- Ouroboros Peras adds an invariant relating epoch size and Peras voting round lengths:
192+
-- > epochSize % perasRoundLength == 0
193+
-- i.e. the round length should divide the epoch size
185194
data EraSummary = EraSummary
186195
{ eraStart :: !Bound
187196
-- ^ Inclusive lower bound
@@ -472,6 +481,17 @@ invariantSummary = \(Summary summary) ->
472481
, " (INV-2b)"
473482
]
474483

484+
unless
485+
( (unEpochSize $ eraEpochSize curParams) `mod` (unPerasRoundLength $ eraPerasRoundLength curParams)
486+
/= 0
487+
) $
488+
throwError $
489+
mconcat
490+
[ "Invalid Peras round length "
491+
, show curSummary
492+
, " (Peras round length does not divide epoch size)"
493+
]
494+
475495
go curEnd next
476496
where
477497
curStart :: Bound
@@ -486,17 +506,19 @@ invariantSummary = \(Summary summary) ->
486506
instance Serialise Bound where
487507
encode Bound{..} =
488508
mconcat
489-
[ encodeListLen 3
509+
[ encodeListLen 4
490510
, encode boundTime
491511
, encode boundSlot
492512
, encode boundEpoch
513+
, encode boundPerasRound
493514
]
494515

495516
decode = do
496-
enforceSize "Bound" 3
517+
enforceSize "Bound" 4
497518
boundTime <- decode
498519
boundSlot <- decode
499520
boundEpoch <- decode
521+
boundPerasRound <- decode
500522
return Bound{..}
501523

502524
instance Serialise EraEnd where

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/History/Util.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,8 +2,10 @@ module Ouroboros.Consensus.HardFork.History.Util
22
( -- * Adding and subtracting slots/epochs
33
addEpochs
44
, addSlots
5+
, addPerasRounds
56
, countEpochs
67
, countSlots
8+
, countPerasRounds
79
, subSlots
810
) where
911

@@ -26,6 +28,9 @@ subSlots n (SlotNo x) = assert (x >= n) $ SlotNo (x - n)
2628
addEpochs :: Word64 -> EpochNo -> EpochNo
2729
addEpochs n (EpochNo x) = EpochNo (x + n)
2830

31+
addPerasRounds :: Word64 -> PerasRoundNo -> PerasRoundNo
32+
addPerasRounds n (PerasRoundNo x) = PerasRoundNo (x + n)
33+
2934
-- | @countSlots to fr@ counts the slots from @fr@ to @to@ (@to >= fr@)
3035
countSlots :: HasCallStack => SlotNo -> SlotNo -> Word64
3136
countSlots (SlotNo to) (SlotNo fr) = assert (to >= fr) $ to - fr
@@ -37,3 +42,8 @@ countEpochs :: HasCallStack => EpochNo -> EpochNo -> Word64
3742
countEpochs (EpochNo to) (EpochNo fr) = assert (to >= fr) $ to - fr
3843
where
3944
_ = keepRedundantConstraint (Proxy :: Proxy HasCallStack)
45+
46+
countPerasRounds :: HasCallStack => PerasRoundNo -> PerasRoundNo -> Word64
47+
countPerasRounds (PerasRoundNo to) (PerasRoundNo fr) = assert (to >= fr) $ to - fr
48+
where
49+
_ = keepRedundantConstraint (Proxy :: Proxy HasCallStack)

ouroboros-consensus/src/unstable-consensus-testlib/Test/Util/Orphans/Arbitrary.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -337,6 +337,7 @@ instance Arbitrary Bound where
337337
<$> (RelativeTime <$> arbitrary)
338338
<*> (SlotNo <$> arbitrary)
339339
<*> (EpochNo <$> arbitrary)
340+
<*> (PerasRoundNo <$> arbitrary)
340341

341342
instance Arbitrary (K Past blk) where
342343
arbitrary = K <$> (Past <$> arbitrary <*> arbitrary)

0 commit comments

Comments
 (0)