1
1
{-# LANGUAGE BlockArguments #-}
2
2
{-# LANGUAGE DerivingStrategies #-}
3
3
{-# LANGUAGE LambdaCase #-}
4
+ {-# LANGUAGE MultiWayIf #-}
4
5
{-# LANGUAGE NamedFieldPuns #-}
5
6
{-# LANGUAGE RecordWildCards #-}
6
7
{-# LANGUAGE ScopedTypeVariables #-}
@@ -25,6 +26,7 @@ import Control.Tracer (Tracer (..), contramapM, traceWith)
25
26
import Data.Foldable (for_ )
26
27
import Data.Map.Strict (Map )
27
28
import qualified Data.Map.Strict as Map
29
+ import Data.Maybe (mapMaybe )
28
30
import Data.Set (Set )
29
31
import qualified Data.Set as Set
30
32
import Data.Time.Clock (secondsToDiffTime )
@@ -37,6 +39,7 @@ import qualified Ouroboros.Network.Mock.Chain as Chain
37
39
38
40
import Ouroboros.Consensus.Block
39
41
import Ouroboros.Consensus.Config
42
+ import Ouroboros.Consensus.Fragment.InFuture (miracle )
40
43
import Ouroboros.Consensus.Storage.ChainDB.API (ChainDB )
41
44
import qualified Ouroboros.Consensus.Storage.ChainDB.API as ChainDB
42
45
import qualified Ouroboros.Consensus.Storage.ChainDB.API.Types.InvalidBlockPunishment as Punishment
@@ -60,17 +63,45 @@ tests = testGroup "FollowerPromptness"
60
63
61
64
prop_followerPromptness :: FollowerPromptnessTestSetup -> Property
62
65
prop_followerPromptness fpts =
66
+ label (bucket (length futureBlocks) (length allBlocks)) $
63
67
counterexample (" Trace:\n " <> unlines (ppTrace <$> traceByTime)) $
64
68
counterexample (condense fpts) $
65
69
counterexample (" Instruction timings: " <> condense followerInstrTimings) $
66
70
counterexample (" Failed to pipeline: " <> condense notPipelined)
67
71
(null notPipelined)
68
72
.&&. counterexample (" Not processed: " <> condense unprocessed)
69
73
(null unprocessed)
74
+ .&&. counterexample (" Future blocks pipelined: " <> condense futureBlocksPipelined)
75
+ (null futureBlocksPipelined)
70
76
where
71
77
FollowerPromptnessOutcome {.. } =
72
78
runSimOrThrow $ runFollowerPromptnessTest fpts
73
79
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
+
74
105
-- Hashes of tentative headers which were not immediately emitted as a
75
106
-- follower instruction.
76
107
notPipelined =
@@ -178,7 +209,10 @@ runFollowerPromptnessTest FollowerPromptnessTestSetup{..} = withRegistry \regist
178
209
mcdbRegistry = registry
179
210
mcdbNodeDBs <- emptyNodeDBs
180
211
let cdbArgs = fromMinimalChainDbArgs MinimalChainDbArgs {.. }
181
- pure $ cdbArgs { cdbTracer = cdbTracer }
212
+ pure $ cdbArgs {
213
+ cdbTracer = cdbTracer
214
+ , cdbCheckInFuture = miracle (pure staticNow) 10
215
+ }
182
216
(_, (chainDB, ChainDBImpl. Internal {intAddBlockRunner})) <-
183
217
allocate
184
218
registry
@@ -198,6 +232,7 @@ data FollowerPromptnessTestSetup = FollowerPromptnessTestSetup {
198
232
securityParam :: SecurityParam
199
233
, chainUpdates :: [ChainUpdate ]
200
234
, artificialDelay :: DiffTime
235
+ , staticNow :: SlotNo
201
236
}
202
237
deriving stock (Show )
203
238
@@ -214,12 +249,20 @@ instance Arbitrary FollowerPromptnessTestSetup where
214
249
-- sufficiently often.
215
250
chainUpdates <- genChainUpdates TentativeChainBehavior securityParam 20
216
251
artificialDelay <- secondsToDiffTime <$> chooseInteger (1 , 10 )
252
+ staticNow <- elements (headerFieldSlot <$> getAllBlocks chainUpdates)
217
253
pure FollowerPromptnessTestSetup {.. }
218
254
255
+
219
256
shrink FollowerPromptnessTestSetup {.. } =
220
257
[ FollowerPromptnessTestSetup {
221
258
chainUpdates = init chainUpdates
259
+ , staticNow = maximum (headerFieldSlot <$> getAllBlocks chainUpdates) - 1
222
260
, ..
223
261
}
224
262
| not $ null chainUpdates
225
263
]
264
+
265
+ getAllBlocks :: [ChainUpdate ] -> [HeaderFields TestBlock ]
266
+ getAllBlocks = mapMaybe $ \ case
267
+ (AddBlock blk) -> Just $ getHeaderFields blk
268
+ _ -> Nothing
0 commit comments