11{-# LANGUAGE BlockArguments #-}
22{-# LANGUAGE DerivingStrategies #-}
33{-# LANGUAGE LambdaCase #-}
4+ {-# LANGUAGE MultiWayIf #-}
45{-# LANGUAGE NamedFieldPuns #-}
56{-# LANGUAGE RecordWildCards #-}
67{-# LANGUAGE ScopedTypeVariables #-}
@@ -25,6 +26,7 @@ import Control.Tracer (Tracer (..), contramapM, traceWith)
2526import Data.Foldable (for_ )
2627import Data.Map.Strict (Map )
2728import qualified Data.Map.Strict as Map
29+ import Data.Maybe (mapMaybe )
2830import Data.Set (Set )
2931import qualified Data.Set as Set
3032import Data.Time.Clock (secondsToDiffTime )
@@ -37,6 +39,7 @@ import qualified Ouroboros.Network.Mock.Chain as Chain
3739
3840import Ouroboros.Consensus.Block
3941import Ouroboros.Consensus.Config
42+ import Ouroboros.Consensus.Fragment.InFuture (miracle )
4043import Ouroboros.Consensus.Storage.ChainDB.API (ChainDB )
4144import qualified Ouroboros.Consensus.Storage.ChainDB.API as ChainDB
4245import qualified Ouroboros.Consensus.Storage.ChainDB.API.Types.InvalidBlockPunishment as Punishment
@@ -60,17 +63,45 @@ tests = testGroup "FollowerPromptness"
6063
6164prop_followerPromptness :: FollowerPromptnessTestSetup -> Property
6265prop_followerPromptness fpts =
66+ label (bucket (length futureBlocks) (length allBlocks)) $
6367 counterexample (" Trace:\n " <> unlines (ppTrace <$> traceByTime)) $
6468 counterexample (condense fpts) $
6569 counterexample (" Instruction timings: " <> condense followerInstrTimings) $
6670 counterexample (" Failed to pipeline: " <> condense notPipelined)
6771 (null notPipelined)
6872 .&&. counterexample (" Not processed: " <> condense unprocessed)
6973 (null unprocessed)
74+ .&&. counterexample (" Future blocks pipelined: " <> condense futureBlocksPipelined)
75+ (null futureBlocksPipelined)
7076 where
7177 FollowerPromptnessOutcome {.. } =
7278 runSimOrThrow $ runFollowerPromptnessTest fpts
7379
80+ bucket x y =
81+ if | x == 0 -> " 0%"
82+ | x == y -> " 100%"
83+ | otherwise -> " (0%, 100%)"
84+
85+ allBlocks = getAllBlocks $ chainUpdates fpts
86+
87+ futureBlocks = [ headerFieldHash hf
88+ | hf <- allBlocks,
89+ headerFieldSlot hf > staticNow fpts
90+ ]
91+
92+ -- Hashes of future blocks that were emitted as a follower
93+ -- instruction. This should be empty since the future check is static. If
94+ -- it weren't it might be the case that once-future blocks are pipelined
95+ -- when they are adopted as part of the chain.
96+ futureBlocksPipelined = futureBlocksFollowedUp followerInstrTimings
97+
98+ -- Hashes of future blocks that were followed up on in the
99+ -- `followUpTimings` argument.
100+ futureBlocksFollowedUp :: Map Time (Set TestHash ) -> [TestHash ]
101+ futureBlocksFollowedUp followUpTimings =
102+ let followUps = Set. unions followUpTimings
103+ in filter (`Set.member` followUps) futureBlocks
104+
74105 -- Hashes of tentative headers which were not immediately emitted as a
75106 -- follower instruction.
76107 notPipelined =
@@ -178,7 +209,10 @@ runFollowerPromptnessTest FollowerPromptnessTestSetup{..} = withRegistry \regist
178209 mcdbRegistry = registry
179210 mcdbNodeDBs <- emptyNodeDBs
180211 let cdbArgs = fromMinimalChainDbArgs MinimalChainDbArgs {.. }
181- pure $ cdbArgs { cdbTracer = cdbTracer }
212+ pure $ cdbArgs {
213+ cdbTracer = cdbTracer
214+ , cdbCheckInFuture = miracle (pure staticNow) 10
215+ }
182216 (_, (chainDB, ChainDBImpl. Internal {intAddBlockRunner})) <-
183217 allocate
184218 registry
@@ -198,6 +232,7 @@ data FollowerPromptnessTestSetup = FollowerPromptnessTestSetup {
198232 securityParam :: SecurityParam
199233 , chainUpdates :: [ChainUpdate ]
200234 , artificialDelay :: DiffTime
235+ , staticNow :: SlotNo
201236 }
202237 deriving stock (Show )
203238
@@ -214,12 +249,20 @@ instance Arbitrary FollowerPromptnessTestSetup where
214249 -- sufficiently often.
215250 chainUpdates <- genChainUpdates TentativeChainBehavior securityParam 20
216251 artificialDelay <- secondsToDiffTime <$> chooseInteger (1 , 10 )
252+ staticNow <- elements (headerFieldSlot <$> getAllBlocks chainUpdates)
217253 pure FollowerPromptnessTestSetup {.. }
218254
255+
219256 shrink FollowerPromptnessTestSetup {.. } =
220257 [ FollowerPromptnessTestSetup {
221258 chainUpdates = init chainUpdates
259+ , staticNow = maximum (headerFieldSlot <$> getAllBlocks chainUpdates) - 1
222260 , ..
223261 }
224262 | not $ null chainUpdates
225263 ]
264+
265+ getAllBlocks :: [ChainUpdate ] -> [HeaderFields TestBlock ]
266+ getAllBlocks = mapMaybe $ \ case
267+ (AddBlock blk) -> Just $ getHeaderFields blk
268+ _ -> Nothing
0 commit comments