Skip to content

Commit 1b0e6d3

Browse files
committed
Linear Leios: reapplyEB
1 parent 6651e6e commit 1b0e6d3

File tree

2 files changed

+90
-32
lines changed

2 files changed

+90
-32
lines changed

simulation/docs/SimulatorModel.md

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -403,19 +403,23 @@ However, in the absence of an attacker, the simulator can simply use the existin
403403
- Despite being unnecessary, having the RB header announce its second body EB would plausibly decrease the average latency of the EBs.
404404
But that decrease should be _very_ minor; with the current overly-coarse multiplexer logic (see [Issue 453](https://github.com/input-output-hk/ouroboros-leios/issues/453)), the EB's `RelayHeader` will arrive immediately after the ChainSync header (which are small), except perhaps during severe congestion.
405405

406-
The Linear Leios simulator adds the following new variables, some of which also require some new threads.
406+
The Linear Leios simulator adds the following new variables, some of which also require new threads.
407407

408408
- `relayLinearEBState`.
409409
As a shortcut, the first Linear Leios simulator will instantiate `Relay` with `RelayHeader InputBlockId` and `InputBlock`.
410410
This is because the IB specified in Short Leios has just a few small fields more than the EB specified in Linear Leios.
411-
- `waitingForLedgerStateAndLinearEbVar` and `ledgerStateAndLinearEbVar`.
412-
An RB that contains an EB cert can be adopted before that EB has been validated.
413-
TODO but it still needs to be applied, which is much cheaper but not free
411+
- `linearLedgerStateVar`, `waitingForLinearLedgerStateVar`, and `waitingForWaitingForLinearLedgerStateVar`.
412+
An RB that contains an EB cert canot be validated without the the certified EB's ledger state.
413+
However, that EB is necessarily certified, so its ledger state can be built comparatively cheaply now, but still not for free.
414+
- The arrival of a Linear EB populates `waitingForWaitingForLinearLedgerStateVar` (and also `waitingForTipVar`; see below).
415+
- The arrival of an RB populates `waitingForLinearLedgerStateVar`, which triggers the `waitingForWaitingForLinearLedgerStateVar` action to populate `linearLedgerStateVar` via the comparatively cheap `reapply` task.
414416
- `waitingForTipVar`.
415-
The Linear EB should be validated the first time its arrived and its parent RB is the tip of the node's selection.
417+
The Linear EB should be validated the first time that both it has arrived and its parent RB is the tip of the node's selection.
416418
- `linearEbsToVoteVar`.
417419
Once a Linear EB has been validated, it should be voted for.
418420
A new custom thread monitors this variable in addition to the clock, so that it can avoid issugin a vote too early or too late.
421+
- `linearEbOfRb`.
422+
A mapping from RB to its announced Linear EB _that has been validated_, which is needed when issuing an RB.
419423

420424
TODO block diffusion pipelining for both RBs and EBs
421425

simulation/src/LeiosProtocol/Short/Node.hs

Lines changed: 81 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -156,9 +156,6 @@ data LeiosNodeState m = LeiosNodeState
156156
, prunedVoteStateToVar :: !(TVar m SlotNo)
157157
-- ^ TODO: refactor into RelayState.
158158
, taskQueue :: !(TaskMultiQueue LeiosNodeTask m)
159-
, waitingForLedgerStateAndLinearEbVar :: !(TVar m (Map EndorseBlockId [STM m ()]))
160-
-- ^ waiting for both to have happened: a Linear EB arrived /and/ its parent RB has been validated
161-
, ledgerStateAndLinearEbVar :: !(TVar m (Map EndorseBlockId ()))
162159
, waitingForTipVar :: !(TVar m (Map (HeaderHash RankingBlock) [STM m ()]))
163160
-- ^ waiting for an RB to be selected
164161
--
@@ -170,6 +167,13 @@ data LeiosNodeState m = LeiosNodeState
170167
, waitingForLedgerStateVar :: !(TVar m (Map (HeaderHash RankingBlock) [STM m ()]))
171168
-- ^ waiting for RB to be validated
172169
, ledgerStateVar :: !(TVar m (Map (HeaderHash RankingBlock) LedgerState))
170+
171+
, linearLedgerStateVar :: !(TVar m (Map EndorseBlockId LedgerState))
172+
, waitingForLinearLedgerStateVar :: !(TVar m (Map EndorseBlockId [STM m ()]))
173+
-- ^ waiting for a Linear EB to be validated
174+
, waitingForWaitingForLinearLedgerStateVar :: !(TVar m (Map EndorseBlockId [STM m ()]))
175+
-- ^ waiting for a Linear EB's ledger state to be demanded
176+
173177
, linearEbOfRb :: !(TVar m (Map (HeaderHash RankingBlock) EndorseBlockId))
174178
-- ^ mapping from RB's to their linear EB that has already been validated
175179
, linearEbsToVoteVar :: !(TVar m (Map SlotNo (Map InputBlockId InputBlock)))
@@ -229,6 +233,7 @@ data ValidationRequest m
229233
| ValidateIBs ![((InputBlockHeader, InputBlockBody), IbDeliveryStage)] !([(InputBlockHeader, InputBlockBody)] -> STM m ())
230234
| ValidateEBS ![EndorseBlock] !([EndorseBlock] -> STM m ())
231235
| ValidateLinearEBs ![InputBlock] !([(EndorseBlockId, InputBlock)] -> STM m ())
236+
| ReapplyLinearEB !InputBlock !(STM m ())
232237
| ValidateVotes ![VoteMsg] !UTCTime !([VoteMsg] -> STM m ())
233238

234239
--------------------------------------------------------------
@@ -481,19 +486,52 @@ newLeiosNodeState cfg = do
481486
relayVoteState <- newRelayState
482487
prunedVoteStateToVar <- newTVarIO (toEnum 0)
483488
ibsNeededForEBVar <- newTVarIO Map.empty
489+
waitingForWaitingForLinearLedgerStateVar <- newTVarIO Map.empty
490+
waitingForLinearLedgerStateVar <- newTVarIO Map.empty
491+
linearLedgerStateVar <- newTVarIO Map.empty
484492
linearEbOfRb <- newTVarIO Map.empty
485493
ledgerStateVar <- newTVarIO Map.empty
486494
waitingForRBVar <- newTVarIO Map.empty
487495
waitingForLedgerStateVar <- newTVarIO Map.empty
488-
waitingForLedgerStateAndLinearEbVar <- newTVarIO Map.empty
489496
waitingForTipVar <- newTVarIO Map.empty
490-
ledgerStateAndLinearEbVar <- newTVarIO Map.empty
491497
taskQueue <- atomically $ newTaskMultiQueue cfg.processingQueueBound
492498
votesForEBVar <- newTVarIO Map.empty
493499
linearEbsToVoteVar <- newTVarIO Map.empty
494500
ibsValidationActionsVar <- newTVarIO Map.empty
495501
return $ LeiosNodeState{..}
496502

503+
-- | PREREQUISITE: the parent RB has already been validated
504+
unblockRb ::
505+
forall m.
506+
( MonadMVar m
507+
, MonadFork m
508+
, MonadAsync m
509+
, MonadSTM m
510+
, MonadTime m
511+
, MonadDelay m
512+
) =>
513+
Tracer m LeiosNodeEvent ->
514+
LeiosNodeConfig ->
515+
LeiosNodeState m ->
516+
InputBlock ->
517+
STM m ()
518+
unblockRb tracer cfg leiosState ib = do
519+
let ebId = convertLinearId ib.id
520+
-- If an RB is waiting for this Linear EB's ledger state, then this Linear EB
521+
-- is certified and so we can @reapply@ this ledger state.
522+
waitFor leiosState.waitingForWaitingForLinearLedgerStateVar $ (\m -> [(ebId, [m])]) $ do
523+
linearLedgerState <- readTVar leiosState.linearLedgerStateVar
524+
-- Be a no-op if the Linear EB was already validated (eg for the sake of
525+
-- voting) before any RB demanded it; TODO short fork race condition
526+
case Map.lookup ebId linearLedgerState of
527+
Just LedgerState -> pure ()
528+
Nothing -> do
529+
dispatchValidationSTM tracer cfg leiosState $! ReapplyLinearEB ib $ do
530+
modifyTVar' leiosState.linearLedgerStateVar $ Map.insert ebId LedgerState
531+
case ib.header.rankingBlock of
532+
GenesisHash -> error "invalid Linear EB"
533+
BlockHash hdrHash -> modifyTVar' leiosState.linearEbOfRb $ Map.insert hdrHash ebId
534+
497535
leiosNode ::
498536
forall m.
499537
( MonadMVar m
@@ -533,14 +571,9 @@ leiosNode tracer cfg followers peers = do
533571
let submitLinearEB (map snd -> xs) _deliveryTime completion = do
534572
traceReceived xs EventLinearEB
535573
unless (null xs) $ do
536-
let unblockRb ibId =
537-
modifyTVar' leiosState.ledgerStateAndLinearEbVar (Map.insert (convertLinearId ibId) ())
538-
-- if we have the EB and its parent RB's ledger state, then subsequent RBs are unblocked
539-
--
540-
-- Note that this can happen even if the EB is not validated.
541574
atomically $ forM_ xs $ \ib -> do
542575
waitFor leiosState.waitingForLedgerStateVar
543-
[ (rbHash, [unblockRb ib.id])
576+
[ (rbHash, [unblockRb tracer cfg leiosState ib])
544577
| BlockHash rbHash <- [ib.header.rankingBlock]
545578
]
546579
dispatch $! ValidateLinearEBs xs completion
@@ -616,10 +649,15 @@ leiosNode tracer cfg followers peers = do
616649
(readTVar ledgerStateVar)
617650
waitingForLedgerStateVar
618651

619-
let processWaitingForLedgerStateAndLinearEb =
652+
let processWaitingForLinearLedgerStateVar =
653+
processWaiting'
654+
(readTVar linearLedgerStateVar)
655+
waitingForLinearLedgerStateVar
656+
657+
let processWaitingForWaitingForLinearLedgerStateVar =
620658
processWaiting'
621-
(readTVar ledgerStateAndLinearEbVar)
622-
waitingForLedgerStateAndLinearEbVar
659+
(readTVar waitingForLinearLedgerStateVar)
660+
waitingForWaitingForLinearLedgerStateVar
623661

624662
let processWaitingForTip =
625663
processWaiting'
@@ -631,11 +669,13 @@ leiosNode tracer cfg followers peers = do
631669

632670
let processingThreads =
633671
[ processCPUTasks cfg.processingCores (contramap LeiosNodeEventCPU tracer) leiosState.taskQueue
634-
, processWaitingForRB
635672
, processWaitingForLedgerState
636-
, processWaitingForLedgerStateAndLinearEb
637-
, processWaitingForTip
638673
]
674+
++ if cfg.leios.variant /= Linear then [processWaitingForRB] else
675+
[ processWaitingForWaitingForLinearLedgerStateVar
676+
, processWaitingForLinearLedgerStateVar
677+
, processWaitingForTip
678+
]
639679

640680
blockGenerationThreads <-
641681
if cfg.leios.variant /= Linear then pure [generator tracer cfg leiosState] else do
@@ -999,7 +1039,18 @@ dispatchValidation ::
9991039
ValidationRequest m ->
10001040
m ()
10011041
dispatchValidation tracer cfg leiosState req =
1002-
atomically $ queue =<< go req
1042+
atomically $ dispatchValidationSTM tracer cfg leiosState req
1043+
1044+
dispatchValidationSTM ::
1045+
forall m.
1046+
(MonadMVar m, MonadFork m, MonadAsync m, MonadSTM m, MonadTime m, MonadDelay m) =>
1047+
Tracer m LeiosNodeEvent ->
1048+
LeiosNodeConfig ->
1049+
LeiosNodeState m ->
1050+
ValidationRequest m ->
1051+
STM m ()
1052+
dispatchValidationSTM tracer cfg leiosState req =
1053+
queue =<< go req
10031054
where
10041055
queue = mapM_ (uncurry $ writeTMQueue leiosState.taskQueue)
10051056
labelTask :: (LeiosNodeTask, (String -> CPUTask, m ())) -> (LeiosNodeTask, (CPUTask, m ()))
@@ -1052,7 +1103,7 @@ dispatchValidation tracer cfg leiosState req =
10521103
BlockHash prev
10531104
| Linear <- cfg.leios.variant -> do
10541105
case rb.blockBody.endorseBlocks of
1055-
[ (ebId, _cert) ] -> waitFor leiosState.waitingForLedgerStateAndLinearEbVar [(ebId, [queue [linearTask]])]
1106+
[ (ebId, _cert) ] -> waitFor leiosState.waitingForLinearLedgerStateVar [(ebId, [queue [linearTask]])]
10561107
[] -> waitFor leiosState.waitingForLedgerStateVar [(prev, [queue [linearTask]])]
10571108
o -> error $ "too many certs in an RB: " <> show (length o)
10581109
pure []
@@ -1098,19 +1149,20 @@ dispatchValidation tracer cfg leiosState req =
10981149
-- NOTE: block references are only inspected during voting.
10991150
return [valEB eb completion | eb <- ebs]
11001151
ValidateLinearEBs ibs completion -> do
1101-
let checkForCert :: InputBlockId -> (Bool -> STM m a) -> STM m a
1102-
checkForCert ibId k = do
1152+
let ifNoCert :: InputBlockId -> STM m () -> STM m ()
1153+
ifNoCert ibId k = do
11031154
votesForEB <- readTVar leiosState.votesForEBVar
1104-
k $ case Map.lookup (convertLinearId ibId) votesForEB of
1105-
Just Certified{} -> True
1106-
_ -> False
1155+
case Map.lookup (convertLinearId ibId) votesForEB of
1156+
Just Certified{} -> pure ()
1157+
_ -> k
11071158
waitFor
11081159
leiosState.waitingForTipVar
1109-
[ (rbHash, [do checkForCert ib.id $ \flag -> queue [valLinearEB ib flag completion]])
1160+
[ (rbHash, [ifNoCert ib.id $ queue [valLinearEB ib False completion]])
11101161
| ib <- ibs
11111162
, BlockHash rbHash <- [ib.header.rankingBlock]
11121163
]
11131164
pure []
1165+
ReapplyLinearEB ib completion -> pure [valLinearEB ib True (const completion)]
11141166
ValidateVotes vs deliveryTime completion -> do
11151167
return [valVote v deliveryTime completion | v <- vs]
11161168
traceEnterState :: [a] -> (a -> LeiosEventBlock) -> m ()
@@ -1137,14 +1189,16 @@ generatorSubmitter tracer cfg st =
11371189
submitOne (delay, x) = withDelay delay $
11381190
case x of
11391191
SomeAction Generate.Base (Left (chain, rb)) -> (GenRB,) $ do
1140-
atomically $ addProducedBlock st.praosState.blockFetchControllerState rb
1192+
atomically $ do
1193+
addProducedBlock st.praosState.blockFetchControllerState rb
1194+
modifyTVar' st.ledgerStateVar $ Map.insert (blockHash rb) LedgerState
11411195
traceWith tracer (PraosNodeEvent (PraosNodeEventGenerate rb))
11421196
traceWith tracer (PraosNodeEvent (PraosNodeEventNewTip $ chain :> rb)) -- TODO don't assume the new block is the best block?
11431197
SomeAction Generate.Base (Right ib) -> (GenEB,) $ do
11441198
let ebId = convertLinearId ib.id
11451199
atomically $ do
11461200
modifyTVar' st.relayLinearEBState.relayBufferVar (RB.snocIfNew ebId (RelayHeader ebId ib.slot, ib))
1147-
modifyTVar' st.ledgerStateAndLinearEbVar (Map.insert ebId ())
1201+
unblockRb tracer cfg st ib
11481202
adoptLinearEB cfg st ib
11491203
traceWith tracer (LeiosNodeEvent Generate (EventLinearEB ib))
11501204
SomeAction Generate.Propose{} ib -> (GenIB,) $ do

0 commit comments

Comments
 (0)