Skip to content

Commit 14229b9

Browse files
agustinmistaamesgengeo2atbagrel1nbacquey
committed
Store most recent cert in the PerasCertDB
This commit adds a method to the PerasCertDB API to retrieve the latest certificate seen. This is certificate needed to implement the Peras voting and must be kept around even after garbage collection. Because of this, we extend the internal state of the PerasCertDB to store this special certificate on the side, and (potentially) update it after new certificates are added to the database. Co-authored-by: Agustin Mista <[email protected]> Co-authored-by: Alexander Esgen <[email protected]> Co-authored-by: Georgy Lukyanov <[email protected]> Co-authored-by: Thomas BAGREL <[email protected]> Co-authored-by: Nicolas BACQUEY <[email protected]>
1 parent 242b1c7 commit 14229b9

File tree

4 files changed

+56
-7
lines changed

4 files changed

+56
-7
lines changed

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/PerasCertDB/API.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,14 @@ data PerasCertDB m blk = PerasCertDB
3535
-- The 'Fingerprint' is updated every time a new certificate is added, but it
3636
-- stays the same when certificates are garbage-collected.
3737
, getCertSnapshot :: STM m (PerasCertSnapshot blk)
38+
, getLatestCertSeen :: STM m (Maybe (WithArrivalTime (ValidatedPerasCert blk)))
39+
-- ^ Get the certificate with the highest round number that has been added to
40+
-- the db since it has been opened. This certificate is not affected by garbage
41+
-- collection, but it's forgotten when the db is closed.
42+
--
43+
-- NOTE: having seen a certificate is a precondition to start voting in every
44+
-- round except for the first one (at origin). As a consequence, only caught-up
45+
-- nodes can actively participate in the Peras protocol for now.
3846
, garbageCollect :: SlotNo -> m ()
3947
-- ^ Garbage-collect state older than the given slot number.
4048
, closeDB :: m ()

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/PerasCertDB/Impl.hs

Lines changed: 21 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -79,6 +79,7 @@ openDB args = do
7979
{ addCert = getEnv1 h implAddCert
8080
, getWeightSnapshot = getEnvSTM h implGetWeightSnapshot
8181
, getCertSnapshot = getEnvSTM h implGetCertSnapshot
82+
, getLatestCertSeen = getEnvSTM h implGetLatestCertSeen
8283
, garbageCollect = getEnv1 h implGarbageCollect
8384
, closeDB = implCloseDB h
8485
}
@@ -170,18 +171,22 @@ implAddCert env cert = do
170171
if Map.member roundNo pvcsCerts
171172
then pure PerasCertAlreadyInDB
172173
else do
174+
let pvcsCerts' = Map.insert roundNo cert pvcsCerts
173175
let pvcsLastTicketNo' = succ pvcsLastTicketNo
174176
writeTVar pcdbVolatileState $
175177
WithFingerprint
176178
PerasVolatileCertState
177179
{ pvcsCerts =
178-
Map.insert roundNo cert pvcsCerts
180+
pvcsCerts'
179181
, -- Note that the same block might be boosted by multiple points.
180182
pvcsWeightByPoint =
181183
addToPerasWeightSnapshot boostedPt (getPerasCertBoost cert) pvcsWeightByPoint
182184
, pvcsCertsByTicket =
183185
Map.insert pvcsLastTicketNo' cert pvcsCertsByTicket
184-
, pvcsLastTicketNo = pvcsLastTicketNo'
186+
, pvcsLastTicketNo =
187+
pvcsLastTicketNo'
188+
, pvcsLatestCertSeen =
189+
snd <$> Map.lookupMax pvcsCerts'
185190
}
186191
(succ fp)
187192
pure AddedPerasCertToDB
@@ -220,6 +225,14 @@ implGetCertSnapshot PerasCertDbEnv{pcdbVolatileState} =
220225
snd $ Map.split ticketNo pvcsCertsByTicket
221226
}
222227

228+
implGetLatestCertSeen ::
229+
IOLike m =>
230+
PerasCertDbEnv m blk -> STM m (Maybe (WithArrivalTime (ValidatedPerasCert blk)))
231+
implGetLatestCertSeen PerasCertDbEnv{pcdbVolatileState} =
232+
readTVar pcdbVolatileState
233+
<&> forgetFingerprint
234+
<&> pvcsLatestCertSeen
235+
223236
implGarbageCollect ::
224237
forall m blk.
225238
IOLike m =>
@@ -236,12 +249,14 @@ implGarbageCollect PerasCertDbEnv{pcdbVolatileState} slot =
236249
, pvcsWeightByPoint
237250
, pvcsLastTicketNo
238251
, pvcsCertsByTicket
252+
, pvcsLatestCertSeen
239253
} =
240254
PerasVolatileCertState
241255
{ pvcsCerts = Map.filter keepCert pvcsCerts
242256
, pvcsWeightByPoint = prunePerasWeightSnapshot slot pvcsWeightByPoint
243257
, pvcsCertsByTicket = Map.filter keepCert pvcsCertsByTicket
244258
, pvcsLastTicketNo = pvcsLastTicketNo
259+
, pvcsLatestCertSeen = pvcsLatestCertSeen
245260
}
246261
where
247262
keepCert cert =
@@ -267,6 +282,9 @@ data PerasVolatileCertState blk = PerasVolatileCertState
267282
, pvcsLastTicketNo :: !PerasCertTicketNo
268283
-- ^ The most recent 'PerasCertTicketNo' (or 'zeroPerasCertTicketNo'
269284
-- otherwise).
285+
, pvcsLatestCertSeen :: !(Maybe (WithArrivalTime (ValidatedPerasCert blk)))
286+
-- ^ The certificate with the highest round number that has been added to the
287+
-- db since it has been opened.
270288
}
271289
deriving stock (Show, Generic)
272290
deriving anyclass NoThunks
@@ -279,6 +297,7 @@ initialPerasVolatileCertState =
279297
, pvcsWeightByPoint = emptyPerasWeightSnapshot
280298
, pvcsCertsByTicket = Map.empty
281299
, pvcsLastTicketNo = zeroPerasCertTicketNo
300+
, pvcsLatestCertSeen = Nothing
282301
}
283302
(Fingerprint 0)
284303

@@ -303,7 +322,6 @@ invariantForPerasVolatileCertState pvcs = do
303322
<> " > "
304323
<> show pvcsLastTicketNo
305324
where
306-
PerasVolatileCertState _ _ _ _keep = forgetFingerprint pvcs
307325
PerasVolatileCertState
308326
{ pvcsCerts
309327
, pvcsWeightByPoint

ouroboros-consensus/test/storage-test/Test/Ouroboros/Storage/PerasCertDB/Model.hs

Lines changed: 15 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module Test.Ouroboros.Storage.PerasCertDB.Model
1111
, closeDB
1212
, addCert
1313
, getWeightSnapshot
14+
, getLatestCertSeen
1415
, garbageCollect
1516
, hasRoundNo
1617
) where
@@ -19,35 +20,40 @@ import Data.Set (Set)
1920
import qualified Data.Set as Set
2021
import GHC.Generics (Generic)
2122
import Ouroboros.Consensus.Block
22-
import Ouroboros.Consensus.BlockchainTime.WallClock.Types (WithArrivalTime)
23+
import Ouroboros.Consensus.BlockchainTime.WallClock.Types (WithArrivalTime, forgetArrivalTime)
2324
import Ouroboros.Consensus.Peras.Weight
2425
( PerasWeightSnapshot
2526
, mkPerasWeightSnapshot
2627
)
28+
import Ouroboros.Consensus.Util (safeMaximumOn)
2729

2830
data Model blk = Model
2931
{ certs :: Set (WithArrivalTime (ValidatedPerasCert blk))
32+
, latestCertSeen :: Maybe (WithArrivalTime (ValidatedPerasCert blk))
3033
, open :: Bool
3134
}
3235
deriving Generic
3336

3437
deriving instance StandardHash blk => Show (Model blk)
3538

3639
initModel :: Model blk
37-
initModel = Model{open = False, certs = Set.empty}
40+
initModel = Model{open = False, certs = Set.empty, latestCertSeen = Nothing}
3841

3942
openDB :: Model blk -> Model blk
4043
openDB model = model{open = True}
4144

4245
closeDB :: Model blk -> Model blk
43-
closeDB _ = Model{open = False, certs = Set.empty}
46+
closeDB _ = Model{open = False, certs = Set.empty, latestCertSeen = Nothing}
4447

4548
addCert ::
4649
StandardHash blk =>
4750
Model blk -> WithArrivalTime (ValidatedPerasCert blk) -> Model blk
4851
addCert model@Model{certs} cert
4952
| certs `hasRoundNo` cert = model
50-
| otherwise = model{certs = Set.insert cert certs}
53+
| otherwise = model{certs = certs', latestCertSeen = safeMaximumOn roundNo (Set.toList certs')}
54+
where
55+
certs' = Set.insert cert certs
56+
roundNo = getPerasCertRound . forgetArrivalTime
5157

5258
hasRoundNo ::
5359
Set (WithArrivalTime (ValidatedPerasCert blk)) ->
@@ -65,6 +71,11 @@ getWeightSnapshot Model{certs} =
6571
| cert <- Set.toList certs
6672
]
6773

74+
getLatestCertSeen ::
75+
Model blk -> Maybe (WithArrivalTime (ValidatedPerasCert blk))
76+
getLatestCertSeen Model{latestCertSeen} =
77+
latestCertSeen
78+
6879
garbageCollect :: SlotNo -> Model blk -> Model blk
6980
garbageCollect slot model@Model{certs} =
7081
model{certs = Set.filter keepCert certs}

ouroboros-consensus/test/storage-test/Test/Ouroboros/Storage/PerasCertDB/StateMachine.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -72,6 +72,7 @@ instance StateModel Model where
7272
CloseDB :: Action Model ()
7373
AddCert :: WithArrivalTime (ValidatedPerasCert TestBlock) -> Action Model AddPerasCertResult
7474
GetWeightSnapshot :: Action Model (PerasWeightSnapshot TestBlock)
75+
GetLatestCertSeen :: Action Model (Maybe (WithArrivalTime (ValidatedPerasCert TestBlock)))
7576
GarbageCollect :: SlotNo -> Action Model ()
7677

7778
arbitraryAction _ (Model model)
@@ -80,6 +81,7 @@ instance StateModel Model where
8081
[ (1, pure $ Some CloseDB)
8182
, (20, Some <$> genAddCert)
8283
, (20, pure $ Some GetWeightSnapshot)
84+
, (10, pure $ Some GetLatestCertSeen)
8385
, (5, Some . GarbageCollect . SlotNo <$> arbitrary)
8486
]
8587
| otherwise = pure $ Some OpenDB
@@ -128,6 +130,7 @@ instance StateModel Model where
128130
CloseDB -> Model.closeDB model
129131
AddCert cert -> Model.addCert model cert
130132
GetWeightSnapshot -> model
133+
GetLatestCertSeen -> model
131134
GarbageCollect slot -> Model.garbageCollect slot model
132135

133136
precondition (Model model) = \case
@@ -143,6 +146,7 @@ instance StateModel Model where
143146
where
144147
p cert' = getPerasCertRound cert /= getPerasCertRound cert' || cert == cert'
145148
GetWeightSnapshot -> True
149+
GetLatestCertSeen -> True
146150
GarbageCollect _slot -> True
147151

148152
deriving stock instance Show (Action Model a)
@@ -165,6 +169,9 @@ instance RunModel Model (StateT (PerasCertDB IO TestBlock) IO) where
165169
GetWeightSnapshot -> do
166170
perasCertDB <- get
167171
lift $ atomically $ forgetFingerprint <$> PerasCertDB.getWeightSnapshot perasCertDB
172+
GetLatestCertSeen -> do
173+
perasCertDB <- get
174+
lift $ atomically $ PerasCertDB.getLatestCertSeen perasCertDB
168175
GarbageCollect slot -> do
169176
perasCertDB <- get
170177
lift $ PerasCertDB.garbageCollect perasCertDB slot
@@ -180,6 +187,11 @@ instance RunModel Model (StateT (PerasCertDB IO TestBlock) IO) where
180187
counterexamplePost $ "Model: " <> show expected
181188
counterexamplePost $ "SUT: " <> show actual
182189
pure $ expected == actual
190+
postcondition (Model model, _) GetLatestCertSeen _ actual = do
191+
let expected = Model.getLatestCertSeen model
192+
counterexamplePost $ "Model: " <> show expected
193+
counterexamplePost $ "SUT: " <> show actual
194+
pure $ expected == actual
183195
postcondition _ _ _ _ = pure True
184196

185197
monitoring (Model model, _) (AddCert cert) _ _ prop =

0 commit comments

Comments
 (0)