Skip to content

Commit f319440

Browse files
committed
ThreadNet: factor out TestSetup
1 parent 6dd15ad commit f319440

File tree

5 files changed

+125
-249
lines changed

5 files changed

+125
-249
lines changed

ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -454,6 +454,7 @@ test-suite cardano-test
454454
Test.Consensus.Cardano.Translation
455455
Test.ThreadNet.AllegraMary
456456
Test.ThreadNet.Cardano
457+
Test.ThreadNet.EraCrossingInfra
457458
Test.ThreadNet.MaryAlonzo
458459
Test.ThreadNet.ShelleyAllegra
459460

ouroboros-consensus-cardano/test/cardano-test/Test/ThreadNet/AllegraMary.hs

Lines changed: 4 additions & 83 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@
1414
module Test.ThreadNet.AllegraMary (tests) where
1515

1616
import qualified Cardano.Ledger.Api.Transition as L
17-
import Cardano.Ledger.BaseTypes (nonZero, unNonZero)
17+
import Cardano.Ledger.BaseTypes (unNonZero)
1818
import qualified Cardano.Ledger.BaseTypes as SL
1919
import qualified Cardano.Ledger.Shelley.Core as SL
2020
import qualified Cardano.Protocol.TPraos.OCert as SL
@@ -29,18 +29,12 @@ import Data.Set (Set)
2929
import qualified Data.Set as Set
3030
import Data.Word (Word64)
3131
import Lens.Micro ((^.))
32-
import Ouroboros.Consensus.BlockchainTime
3332
import Ouroboros.Consensus.Cardano.Condense ()
3433
import Ouroboros.Consensus.Cardano.Node (TriggerHardFork (..))
3534
import Ouroboros.Consensus.Config.SecurityParam
36-
import Ouroboros.Consensus.HardFork.Combinator.Serialisation.Common
37-
( isHardForkNodeToNodeEnabled
38-
)
3935
import Ouroboros.Consensus.Ledger.SupportsMempool (extractTxs)
40-
import Ouroboros.Consensus.Node.NetworkProtocolVersion
4136
import Ouroboros.Consensus.Node.ProtocolInfo
4237
import Ouroboros.Consensus.NodeId
43-
import Ouroboros.Consensus.Protocol.TPraos (TPraos)
4438
import Ouroboros.Consensus.Shelley.Eras
4539
import Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol ()
4640
import Ouroboros.Consensus.Shelley.Node
@@ -51,6 +45,7 @@ import Test.Consensus.Shelley.MockCrypto (MockCrypto)
5145
import Test.QuickCheck
5246
import Test.Tasty
5347
import Test.Tasty.QuickCheck
48+
import Test.ThreadNet.EraCrossingInfra (DualBlock, TestSetup (..))
5449
import Test.ThreadNet.General
5550
import qualified Test.ThreadNet.Infra.Shelley as Shelley
5651
import Test.ThreadNet.Infra.ShelleyBasedHardFork
@@ -65,87 +60,13 @@ import Test.ThreadNet.TxGen.Mary ()
6560
import Test.ThreadNet.Util.Expectations (NumBlocks (..))
6661
import Test.ThreadNet.Util.NodeJoinPlan (trivialNodeJoinPlan)
6762
import Test.ThreadNet.Util.NodeRestarts (noRestarts)
68-
import Test.ThreadNet.Util.NodeToNodeVersion (genVersionFiltered)
6963
import Test.ThreadNet.Util.Seed (runGen)
7064
import qualified Test.Util.BoolProps as BoolProps
7165
import Test.Util.HardFork.Future (EraSize (..), Future (..))
7266
import Test.Util.Orphans.Arbitrary ()
7367
import Test.Util.Slots (NumSlots (..))
7468
import Test.Util.TestEnv
7569

76-
type AllegraMaryBlock =
77-
ShelleyBasedHardForkBlock (TPraos MockCrypto) AllegraEra (TPraos MockCrypto) MaryEra
78-
79-
-- | The varying data of this test
80-
--
81-
-- Note: The Shelley nodes in this test all join, propose an update, and endorse
82-
-- it literally as soon as possible. Therefore, if the test reaches the end of
83-
-- the first epoch, the proposal will be adopted.
84-
data TestSetup = TestSetup
85-
{ setupD :: Shelley.DecentralizationParam
86-
, setupHardFork :: Bool
87-
-- ^ whether the proposal should trigger a hard fork or not
88-
, setupInitialNonce :: SL.Nonce
89-
-- ^ the initial Shelley 'SL.ticknStateEpochNonce'
90-
--
91-
-- We vary it to ensure we explore different leader schedules.
92-
, setupK :: SecurityParam
93-
, setupPartition :: Partition
94-
, setupSlotLength :: SlotLength
95-
, setupTestConfig :: TestConfig
96-
, setupVersion :: (NodeToNodeVersion, BlockNodeToNodeVersion AllegraMaryBlock)
97-
}
98-
deriving Show
99-
100-
instance Arbitrary TestSetup where
101-
arbitrary = do
102-
setupD <-
103-
arbitrary
104-
-- The decentralization parameter cannot be 0 in the first
105-
-- Shelley epoch, since stake pools can only be created and
106-
-- delegated to via Shelley transactions.
107-
`suchThat` ((/= 0) . Shelley.decentralizationParamToRational)
108-
setupK <- SecurityParam <$> choose (8, 10) `suchThatMap` nonZero
109-
-- If k < 8, common prefix violations become too likely in
110-
-- Praos mode for thin overlay schedules (ie low d), even for
111-
-- f=0.2.
112-
113-
setupInitialNonce <- genNonce
114-
115-
setupSlotLength <- arbitrary
116-
117-
let epochSize = EpochSize $ shelleyEpochSize setupK
118-
setupTestConfig <-
119-
genTestConfig
120-
setupK
121-
(epochSize, epochSize)
122-
let TestConfig{numCoreNodes, numSlots} = setupTestConfig
123-
124-
setupHardFork <- frequency [(49, pure True), (1, pure False)]
125-
126-
-- TODO How reliable is the Byron-based partition duration logic when
127-
-- reused for Shelley?
128-
setupPartition <- genPartition numCoreNodes numSlots setupK
129-
130-
setupVersion <-
131-
genVersionFiltered
132-
isHardForkNodeToNodeEnabled
133-
(Proxy @AllegraMaryBlock)
134-
135-
pure
136-
TestSetup
137-
{ setupD
138-
, setupHardFork
139-
, setupInitialNonce
140-
, setupK
141-
, setupPartition
142-
, setupSlotLength
143-
, setupTestConfig
144-
, setupVersion
145-
}
146-
147-
-- TODO shrink
148-
14970
tests :: TestTree
15071
tests =
15172
testGroup
@@ -158,7 +79,7 @@ tests =
15879
Nightly -> tree
15980
_ -> adjustQuickCheckTests (`div` 10) tree
16081

161-
prop_simple_allegraMary_convergence :: TestSetup -> Property
82+
prop_simple_allegraMary_convergence :: TestSetup AllegraEra MaryEra -> Property
16283
prop_simple_allegraMary_convergence
16384
TestSetup
16485
{ setupD
@@ -235,7 +156,7 @@ prop_simple_allegraMary_convergence
235156
, version = setupVersion
236157
}
237158

238-
testOutput :: TestOutput AllegraMaryBlock
159+
testOutput :: TestOutput (DualBlock AllegraEra MaryEra)
239160
testOutput =
240161
runTestNetwork
241162
setupTestConfig
Lines changed: 112 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,112 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE DerivingVia #-}
3+
{-# LANGUAGE FlexibleContexts #-}
4+
{-# LANGUAGE FlexibleInstances #-}
5+
{-# LANGUAGE NamedFieldPuns #-}
6+
{-# LANGUAGE ScopedTypeVariables #-}
7+
{-# LANGUAGE StandaloneDeriving #-}
8+
{-# LANGUAGE TypeApplications #-}
9+
{-# LANGUAGE TypeFamilies #-}
10+
{-# LANGUAGE UndecidableInstances #-}
11+
{-# OPTIONS_GHC -Wno-orphans #-}
12+
13+
module Test.ThreadNet.EraCrossingInfra (TestSetup (..), DualBlock) where
14+
15+
import Cardano.Ledger.BaseTypes (nonZero)
16+
import qualified Cardano.Ledger.BaseTypes as SL
17+
import Cardano.Slotting.Slot (EpochSize (..))
18+
import Data.Proxy (Proxy (..))
19+
import Ouroboros.Consensus.BlockchainTime
20+
import Ouroboros.Consensus.Cardano.Condense ()
21+
import Ouroboros.Consensus.Config.SecurityParam
22+
import Ouroboros.Consensus.HardFork.Combinator.Serialisation.Common
23+
( isHardForkNodeToNodeEnabled
24+
)
25+
import Ouroboros.Consensus.Node.NetworkProtocolVersion
26+
import Ouroboros.Consensus.Protocol.TPraos (TPraos)
27+
import Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol ()
28+
import Test.Consensus.Shelley.MockCrypto (MockCrypto)
29+
import Test.QuickCheck
30+
import Test.ThreadNet.General
31+
import qualified Test.ThreadNet.Infra.Shelley as Shelley
32+
import Test.ThreadNet.Infra.ShelleyBasedHardFork
33+
import Test.ThreadNet.Infra.TwoEras
34+
import Test.ThreadNet.TxGen.Allegra ()
35+
import Test.ThreadNet.Util.NodeToNodeVersion (genVersionFiltered)
36+
import Test.Util.Orphans.Arbitrary ()
37+
38+
-- | A hard-fork block for two Shelley-based eras
39+
type DualBlock era1 era2 =
40+
ShelleyBasedHardForkBlock (TPraos MockCrypto) era1 (TPraos MockCrypto) era2
41+
42+
-- | The varying data of the tests crossing between Shelley-based eras
43+
--
44+
-- Note: The Shelley nodes in this test all join, propose an update, and endorse
45+
-- it literally as soon as possible. Therefore, if the test reaches the end of
46+
-- the first epoch, the proposal will be adopted.
47+
data TestSetup era1 era2 = TestSetup
48+
{ setupD :: Shelley.DecentralizationParam
49+
, setupHardFork :: Bool
50+
-- ^ whether the proposal should trigger a hard fork or not
51+
, setupInitialNonce :: SL.Nonce
52+
-- ^ the initial Shelley 'SL.ticknStateEpochNonce'
53+
--
54+
-- We vary it to ensure we explore different leader schedules.
55+
, setupK :: SecurityParam
56+
, setupPartition :: Partition
57+
, setupSlotLength :: SlotLength
58+
, setupTestConfig :: TestConfig
59+
, setupVersion :: (NodeToNodeVersion, BlockNodeToNodeVersion (DualBlock era1 era2))
60+
}
61+
62+
deriving instance Show (TestSetup era1 era2)
63+
64+
instance
65+
SupportedNetworkProtocolVersion (DualBlock era1 era2) =>
66+
Arbitrary (TestSetup era1 era2)
67+
where
68+
arbitrary = do
69+
setupD <-
70+
arbitrary
71+
-- The decentralization parameter cannot be 0 in the first
72+
-- Shelley epoch, since stake pools can only be created and
73+
-- delegated to via Shelley transactions.
74+
`suchThat` ((/= 0) . Shelley.decentralizationParamToRational)
75+
setupK <- SecurityParam <$> choose (8, 10) `suchThatMap` nonZero
76+
-- If k < 8, common prefix violations become too likely in
77+
-- Praos mode for thin overlay schedules (ie low d), even for
78+
-- f=0.2.
79+
80+
setupInitialNonce <- genNonce
81+
82+
setupSlotLength <- arbitrary
83+
84+
let epochSize = EpochSize $ shelleyEpochSize setupK
85+
setupTestConfig <-
86+
genTestConfig
87+
setupK
88+
(epochSize, epochSize)
89+
let TestConfig{numCoreNodes, numSlots} = setupTestConfig
90+
91+
setupHardFork <- frequency [(49, pure True), (1, pure False)]
92+
93+
-- TODO How reliable is the Byron-based partition duration logic when
94+
-- reused for Shelley?
95+
setupPartition <- genPartition numCoreNodes numSlots setupK
96+
97+
setupVersion <-
98+
genVersionFiltered
99+
isHardForkNodeToNodeEnabled
100+
(Proxy @(DualBlock era1 era2))
101+
102+
pure
103+
TestSetup
104+
{ setupD
105+
, setupHardFork
106+
, setupInitialNonce
107+
, setupK
108+
, setupPartition
109+
, setupSlotLength
110+
, setupTestConfig
111+
, setupVersion
112+
}

0 commit comments

Comments
 (0)