@@ -10,13 +10,12 @@ module Test.Consensus.Genesis.Setup.GenChains (
1010 , genChainsWithExtraHonestPeers
1111 ) where
1212
13- import Cardano.Slotting.Time (SlotLength , getSlotLength ,
14- slotLengthFromSec )
13+ import Cardano.Slotting.Time (slotLengthFromSec )
1514import Control.Monad (replicateM )
1615import qualified Control.Monad.Except as Exn
1716import Data.List as List (foldl' )
1817import Data.Proxy (Proxy (.. ))
19- import Data.Time.Clock (DiffTime , secondsToDiffTime )
18+ import Data.Time.Clock (DiffTime )
2019import qualified Data.Vector.Unboxed as Vector
2120import Data.Word (Word8 )
2221import Ouroboros.Consensus.Block.Abstract hiding (Header )
@@ -110,7 +109,7 @@ genChains = genChainsWithExtraHonestPeers (pure 0)
110109-- However, in the future it could also be used to generate "short forks" near the tip of the trunk.
111110genChainsWithExtraHonestPeers :: QC. Gen Word -> QC. Gen Word -> QC. Gen (GenesisTest TestBlock () )
112111genChainsWithExtraHonestPeers genNumExtraHonest genNumForks = do
113- (asc , honestRecipe, someHonestChainSchema) <- genHonestChainSchema
112+ (_ , honestRecipe, someHonestChainSchema) <- genHonestChainSchema
114113
115114 H. SomeHonestChainSchema _ _ honestChainSchema <- pure someHonestChainSchema
116115 let ChainSchema _ vH = honestChainSchema
@@ -128,8 +127,8 @@ genChainsWithExtraHonestPeers genNumExtraHonest genNumForks = do
128127 gtGenesisWindow = GenesisWindow (fromIntegral scg),
129128 gtForecastRange = ForecastRange (fromIntegral scg), -- REVIEW: Do we want to generate those randomly?
130129 gtDelay = delta,
131- gtSlotLength,
132- gtChainSyncTimeouts = chainSyncTimeouts gtSlotLength asc ,
130+ gtSlotLength = slotLengthFromSec 20 ,
131+ gtChainSyncTimeouts = chainSyncTimeouts,
133132 gtBlockFetchTimeouts = blockFetchTimeouts,
134133 gtLoPBucketParams = LoPBucketParams { lbpCapacity = 50 , lbpRate = 10 },
135134 -- These values give little enough leeway (5s) so that some adversaries get disconnected
@@ -143,8 +142,6 @@ genChainsWithExtraHonestPeers genNumExtraHonest genNumForks = do
143142 }
144143
145144 where
146- gtSlotLength = slotLengthFromSec 20
147-
148145 genAdversarialFragment :: [TestBlock ] -> Int -> (Int , [S ]) -> AnchoredFragment TestBlock
149146 genAdversarialFragment goodBlocks forkNo (prefixCount, slotsA)
150147 = mkTestFragment (mkTestBlocks prefix slotsA forkNo)
@@ -169,11 +166,8 @@ genChainsWithExtraHonestPeers genNumExtraHonest genNumForks = do
169166 incSlot :: SlotNo -> TestBlock -> TestBlock
170167 incSlot n b = b { tbSlot = tbSlot b + n }
171168
172- chainSyncTimeouts ::
173- SlotLength ->
174- Asc ->
175- ChainSyncTimeout
176- chainSyncTimeouts t f =
169+ chainSyncTimeouts :: ChainSyncTimeout
170+ chainSyncTimeouts =
177171 ChainSyncTimeout
178172 { canAwaitTimeout,
179173 intersectTimeout,
@@ -186,21 +180,16 @@ chainSyncTimeouts t f =
186180 intersectTimeout :: Maybe DiffTime
187181 intersectTimeout = shortWait
188182 idleTimeout :: Maybe DiffTime
189- idleTimeout = Just 3673 -- taken from Ouroboros.Consensus.Node.stdChainSyncTimeout
190- -- | The following timeout is derived from the average length of a streak of
191- -- empty slots. If the probability of the election of a leader is @f@ and
192- -- @Y@ is a probability, then a streak of empty slots will be shorter than
193- -- @log (1 - Y) / log (1 - f)@ with probability @Y@. Main net nodes pick a
194- -- random value for @Y@ between 99.9% and 99.999%. For our use case, we
195- -- choose the tightest bound of 99.9%.
183+ -- | The default from 'Ouroboros.Consensus.Node.stdChainSyncTimeout' is
184+ -- 3673s, which is virtually infinite, so let us make it actually infinite
185+ -- for our test environment.
186+ idleTimeout = Nothing
187+ -- | The 'mustReplyTimeout' must be disabled in our context, because the
188+ -- chains are finite, and therefore an honest peer can only serve it all,
189+ -- then send 'MsgAwaitReply' (therefore entering 'StMustReply'), and then
190+ -- stall forever, and it must not be killed for it.
196191 mustReplyTimeout :: Maybe DiffTime
197- mustReplyTimeout =
198- Just $
199- secondsToDiffTime $
200- round $
201- realToFrac (getSlotLength t)
202- * log (1 - 0.999 )
203- / log (1 - ascVal f)
192+ mustReplyTimeout = Nothing
204193
205194blockFetchTimeouts :: BlockFetchTimeout
206195blockFetchTimeouts =
0 commit comments