Skip to content

Commit f6edc1e

Browse files
authored
Merge pull request IntersectMBO#5645 from IntersectMBO/smelc/testnet-allow-passing-config-files
cardano-testnet: allow to pass genesis files
2 parents 87aa5e6 + 73c883d commit f6edc1e

File tree

16 files changed

+109
-51
lines changed

16 files changed

+109
-51
lines changed

cardano-node-chairman/test/Spec/Chairman/Cardano.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,6 @@ hprop_chairman :: H.Property
1616
hprop_chairman = H.integrationRetryWorkspace 2 "cardano-chairman" $ \tempAbsPath' -> do
1717
conf <- H.mkConf tempAbsPath'
1818

19-
allNodes <- fmap H.nodeName . H.allNodes <$> H.cardanoTestnet H.cardanoDefaultTestnetOptions conf
19+
allNodes <- fmap H.nodeName . H.allNodes <$> H.cardanoTestnetDefault H.cardanoDefaultTestnetOptions conf
2020

2121
chairmanOver 120 50 conf allNodes

cardano-testnet/src/Cardano/Testnet.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module Cardano.Testnet (
55

66
-- ** Start a testnet
77
cardanoTestnet,
8+
cardanoTestnetDefault,
89

910
-- ** Testnet options
1011
CardanoTestnetOptions(..),

cardano-testnet/src/Parsers/Run.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,4 +52,4 @@ runTestnetCmd = \case
5252

5353
runCardanoOptions :: CardanoTestnetOptions -> IO ()
5454
runCardanoOptions options =
55-
runTestnet $ cardanoTestnet options
55+
runTestnet $ cardanoTestnetDefault options

cardano-testnet/src/Testnet/Components/Configuration.hs

Lines changed: 21 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE GADTs #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
23
{-# LANGUAGE OverloadedStrings #-}
34
{-# LANGUAGE TypeApplications #-}
45

@@ -8,6 +9,8 @@ module Testnet.Components.Configuration
89
, createSPOGenesisAndFiles
910
, mkTopologyConfig
1011
, numSeededUTxOKeys
12+
, NumPools
13+
, numPools
1114
) where
1215

1316
import Cardano.Api.Pretty
@@ -30,7 +33,6 @@ import qualified Data.ByteString.Lazy as LBS
3033
import Data.Char (toLower)
3134
import qualified Data.List as List
3235
import Data.String
33-
import Data.Time
3436
import GHC.Stack (HasCallStack)
3537
import qualified GHC.Stack as GHC
3638
import Lens.Micro
@@ -42,11 +44,13 @@ import qualified Hedgehog.Extras.Stock.Time as DTC
4244
import qualified Hedgehog.Extras.Test.Base as H
4345
import qualified Hedgehog.Extras.Test.File as H
4446

47+
import Cardano.Api.Ledger (StandardCrypto)
48+
import Data.Word (Word32)
4549
import Testnet.Defaults
4650
import Testnet.Filepath
4751
import Testnet.Process.Run (execCli_)
4852
import Testnet.Property.Utils
49-
import Testnet.Start.Types
53+
import Testnet.Start.Types (CardanoTestnetOptions (..))
5054

5155

5256
createConfigYaml
@@ -78,35 +82,35 @@ createConfigYaml (TmpAbsolutePath tempAbsPath') anyCardanoEra' = GHC.withFrozenC
7882
numSeededUTxOKeys :: Int
7983
numSeededUTxOKeys = 3
8084

85+
newtype NumPools = NumPools Int
86+
87+
numPools :: CardanoTestnetOptions -> NumPools
88+
numPools CardanoTestnetOptions { cardanoNodes } = NumPools $ length cardanoNodes
89+
8190
createSPOGenesisAndFiles
8291
:: (MonadTest m, MonadCatch m, MonadIO m, HasCallStack)
83-
=> CardanoTestnetOptions
84-
-> UTCTime -- ^ Start time
92+
=> NumPools -- ^ The number of pools to make
93+
-> AnyCardanoEra -- ^ The era to use
94+
-> ShelleyGenesis StandardCrypto -- ^ The shelley genesis to use.
8595
-> TmpAbsolutePath
8696
-> m FilePath -- ^ Shelley genesis directory
87-
createSPOGenesisAndFiles testnetOptions startTime (TmpAbsolutePath tempAbsPath') = do
97+
createSPOGenesisAndFiles (NumPools numPoolNodes) era shelleyGenesis (TmpAbsolutePath tempAbsPath') = do
8898
let genesisShelleyFpAbs = tempAbsPath' </> defaultShelleyGenesisFp
8999
genesisShelleyDirAbs = takeDirectory genesisShelleyFpAbs
90100
genesisShelleyDir <- H.createDirectoryIfMissing genesisShelleyDirAbs
91-
let testnetMagic = cardanoTestnetMagic testnetOptions
92-
numPoolNodes = length $ cardanoNodes testnetOptions
101+
let testnetMagic = sgNetworkMagic shelleyGenesis
93102
numStakeDelegators = 3
94-
era = cardanoNodeEra testnetOptions
95-
-- TODO: Even this is cumbersome. You need to know where to put the initial
96-
-- shelley genesis for create-testnet-data to use.
103+
startTime = sgSystemStart shelleyGenesis
97104

98105
-- TODO: We need to read the genesis files into Haskell and modify them
99106
-- based on cardano-testnet's cli parameters
100107

101108
-- We create the initial genesis file to avoid having to re-write the genesis file later
102109
-- with the parameters we want. The user must provide genesis files or we will use a default.
103-
-- We should *never* be modifying the genesis file after cardano-testnet is run because this
110+
-- We should *never* be modifying the genesis file after @cardanoTestnet@ is run because this
104111
-- is sure to be a source of confusion if users provide genesis files and we are mutating them
105112
-- without their knowledge.
106-
let shelleyGenesis :: LBS.ByteString
107-
shelleyGenesis = encode $ defaultShelleyGenesis startTime testnetOptions
108-
109-
H.evalIO $ LBS.writeFile genesisShelleyFpAbs shelleyGenesis
113+
H.evalIO $ LBS.writeFile genesisShelleyFpAbs $ encode shelleyGenesis
110114

111115
-- TODO: Remove this rewrite.
112116
-- 50 second epochs
@@ -128,7 +132,7 @@ createSPOGenesisAndFiles testnetOptions startTime (TmpAbsolutePath tempAbsPath')
128132
execCli_
129133
[ convertToEraString era, "genesis", "create-testnet-data"
130134
, "--spec-shelley", genesisShelleyFpAbs
131-
, "--testnet-magic", show @Int testnetMagic
135+
, "--testnet-magic", show @Word32 testnetMagic
132136
, "--pools", show @Int numPoolNodes
133137
, "--supply", "1000000000000"
134138
, "--supply-delegated", "1000000000000"
@@ -138,7 +142,7 @@ createSPOGenesisAndFiles testnetOptions startTime (TmpAbsolutePath tempAbsPath')
138142
, "--out-dir", tempAbsPath'
139143
]
140144

141-
-- Here we move all of the keys etc generated by create-staked
145+
-- Here we move all of the keys etc generated by create-testnet-data
142146
-- for the nodes to use
143147

144148
-- Move all genesis related files

cardano-testnet/src/Testnet/Start/Cardano.hs

Lines changed: 73 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -16,13 +16,11 @@ module Testnet.Start.Cardano
1616
, PaymentKeyPair(..)
1717

1818
, cardanoTestnet
19-
19+
, cardanoTestnetDefault
2020
) where
2121

2222

2323
import Control.Monad
24-
import qualified Control.Monad.Class.MonadTimer.SI as MT
25-
import Control.Monad.IO.Class
2624
import Control.Monad.Trans.Class (lift)
2725
import Control.Monad.Trans.Except (runExceptT)
2826
import Data.Aeson
@@ -43,14 +41,25 @@ import qualified Hedgehog.Extras.Stock.OS as OS
4341
import qualified Hedgehog.Extras.Test.Base as H
4442
import qualified Hedgehog.Extras.Test.File as H
4543

44+
import qualified Testnet.Defaults as Defaults
45+
46+
import Cardano.Api
47+
import Cardano.Api.Ledger (StandardCrypto)
48+
import Cardano.Ledger.Alonzo.Genesis (AlonzoGenesis)
49+
import Cardano.Ledger.Conway.Genesis (ConwayGenesis)
50+
import qualified Control.Monad.Class.MonadTimer.SI as MT
51+
import Control.Monad.IO.Class
52+
import qualified Data.Aeson as Aeson
53+
import Data.Bifunctor (first)
54+
import Data.Time (UTCTime)
55+
import Data.Word (Word32)
4656
import Testnet.Components.Configuration
47-
import Testnet.Defaults
4857
import Testnet.Filepath
4958
import qualified Testnet.Process.Run as H
5059
import Testnet.Process.Run
5160
import qualified Testnet.Property.Assert as H
5261
import Testnet.Property.Checks
53-
import Testnet.Runtime
62+
import Testnet.Runtime as TR hiding (shelleyGenesis)
5463
import qualified Testnet.Start.Byron as Byron
5564
import Testnet.Start.Types
5665

@@ -63,10 +72,11 @@ import Testnet.Start.Types
6372
-- a valid node cluster.
6473
testnetMinimumConfigurationRequirements :: CardanoTestnetOptions -> H.Integration ()
6574
testnetMinimumConfigurationRequirements cTestnetOpts = do
66-
when (length (cardanoNodes cTestnetOpts) < 2) $ do
67-
H.noteShow_ ("Need at least two nodes to run a cluster" :: String)
75+
let actualLength = length (cardanoNodes cTestnetOpts)
76+
when (actualLength < 2) $ do
77+
H.noteShow_ ("Need at least two nodes to run a cluster, but got: " <> show actualLength)
6878
H.noteShow_ cTestnetOpts
69-
H.assert False
79+
H.failure
7080

7181
data ForkPoint
7282
= AtVersion Int
@@ -79,6 +89,19 @@ data ForkPoint
7989
startTimeOffsetSeconds :: DTC.NominalDiffTime
8090
startTimeOffsetSeconds = if OS.isWin32 then 90 else 15
8191

92+
-- | Like 'cardanoTestnet', but using defaults for all configuration files.
93+
-- See 'cardanoTestnet' for additional documentation.
94+
cardanoTestnetDefault :: ()
95+
=> CardanoTestnetOptions
96+
-> Conf
97+
-> H.Integration TestnetRuntime
98+
cardanoTestnetDefault opts conf = do
99+
alonzoGenesis <- H.evalEither $ first prettyError Defaults.defaultAlonzoGenesis
100+
currentTime <- H.noteShowIO DTC.getCurrentTime
101+
startTime <- H.noteShow $ DTC.addUTCTime startTimeOffsetSeconds currentTime
102+
cardanoTestnet
103+
opts conf startTime
104+
(Defaults.defaultShelleyGenesis startTime opts) alonzoGenesis Defaults.defaultConwayGenesis
82105

83106
-- | Setup a number of credentials and pools, like this:
84107
--
@@ -122,13 +145,37 @@ startTimeOffsetSeconds = if OS.isWin32 then 90 else 15
122145
-- > │   └── node-spo{1,2,3}
123146
-- > └── utxo-keys
124147
-- >    └── utxo{1,2,3}.{addr,skey,vkey}
125-
cardanoTestnet :: CardanoTestnetOptions -> Conf -> H.Integration TestnetRuntime
126-
cardanoTestnet testnetOptions Conf {tempAbsPath=TmpAbsolutePath tmpAbsPath} = do
127-
testnetMinimumConfigurationRequirements testnetOptions
128-
void $ H.note OS.os
129-
currentTime <- H.noteShowIO DTC.getCurrentTime
130-
let testnetMagic = cardanoTestnetMagic testnetOptions
148+
cardanoTestnet :: ()
149+
=> CardanoTestnetOptions -- ^ The options to use. Must be consistent with the genesis files.
150+
-> Conf
151+
-> UTCTime -- ^ The starting time. Must be the same as the one in the shelley genesis.
152+
-> ShelleyGenesis StandardCrypto -- ^ The shelley genesis to use, for example 'Defaults.defaultShelleyGenesis'.
153+
-- Some fields are overridden by the accompanying 'CardanoTestnetOptions'.
154+
-> AlonzoGenesis -- ^ The alonzo genesis to use, for example 'Defaults.defaultAlonzoGenesis'.
155+
-> ConwayGenesis StandardCrypto -- ^ The conway genesis to use, for example 'Defaults.defaultConwayGenesis'.
156+
-> H.Integration TestnetRuntime
157+
cardanoTestnet
158+
testnetOptions Conf {tempAbsPath=TmpAbsolutePath tmpAbsPath} startTime
159+
shelleyGenesis alonzoGenesis conwayGenesis = do
160+
let shelleyStartTime = sgSystemStart shelleyGenesis
161+
shelleyTestnetMagic = sgNetworkMagic shelleyGenesis
162+
optionsMagic :: Word32 = fromIntegral $ cardanoTestnetMagic testnetOptions
163+
testnetMagic = cardanoTestnetMagic testnetOptions
131164
numPoolNodes = length $ cardanoNodes testnetOptions
165+
nbPools = numPools testnetOptions
166+
era = cardanoNodeEra testnetOptions
167+
168+
-- Sanity checks
169+
testnetMinimumConfigurationRequirements testnetOptions
170+
when (shelleyStartTime /= startTime) $ do
171+
H.note_ $ "Expected same system start in shelley genesis and parameter, but got " <> show shelleyStartTime <> " and " <> show startTime
172+
H.failure
173+
when (shelleyTestnetMagic /= optionsMagic) $ do
174+
H.note_ $ "Expected same network magic in shelley genesis and parameter, but got " <> show shelleyTestnetMagic <> " and " <> show optionsMagic
175+
H.failure
176+
-- Done with sanity checks
177+
178+
H.note_ OS.os
132179

133180
if all isJust [mconfig | SpoTestnetNodeOptions mconfig _ <- cardanoNodes testnetOptions]
134181
then
@@ -138,10 +185,8 @@ cardanoTestnet testnetOptions Conf {tempAbsPath=TmpAbsolutePath tmpAbsPath} = do
138185
-- See all of the ad hoc file creation/renaming/dir creation etc below.
139186
H.failMessage GHC.callStack "Specifying node configuration files per node not supported yet."
140187
else do
141-
startTime <- H.noteShow $ DTC.addUTCTime startTimeOffsetSeconds currentTime
142-
143188
H.lbsWriteFile (tmpAbsPath </> "byron.genesis.spec.json")
144-
. encode $ defaultByronProtocolParamsJsonValue
189+
. encode $ Defaults.defaultByronProtocolParamsJsonValue
145190

146191
-- Because in Conway the overlay schedule and decentralization parameter
147192
-- are deprecated, we must use the "create-staked" cli command to create
@@ -153,10 +198,18 @@ cardanoTestnet testnetOptions Conf {tempAbsPath=TmpAbsolutePath tmpAbsPath} = do
153198
(tmpAbsPath </> "byron.genesis.spec.json")
154199
(tmpAbsPath </> "byron-gen-command")
155200

156-
_ <- createSPOGenesisAndFiles testnetOptions startTime (TmpAbsolutePath tmpAbsPath)
201+
-- Write Alonzo genesis file
202+
alonzoGenesisJsonFile <- H.noteShow $ tmpAbsPath </> "genesis.alonzo.spec.json"
203+
H.evalIO $ LBS.writeFile alonzoGenesisJsonFile $ Aeson.encode alonzoGenesis
204+
205+
-- Write Conway genesis file
206+
conwayGenesisJsonFile <- H.noteShow $ tmpAbsPath </> "genesis.conway.spec.json"
207+
H.evalIO $ LBS.writeFile conwayGenesisJsonFile $ Aeson.encode conwayGenesis
157208

158209
configurationFile <- H.noteShow $ tmpAbsPath </> "configuration.yaml"
159210

211+
_ <- createSPOGenesisAndFiles nbPools era shelleyGenesis (TmpAbsolutePath tmpAbsPath)
212+
160213
poolKeys <- H.noteShow $ flip fmap [1..numPoolNodes] $ \n ->
161214
PoolNodeKeys
162215
{ poolNodeKeysColdVkey = tmpAbsPath </> "pools" </> "cold" <> show n <> ".vkey"
@@ -213,7 +266,7 @@ cardanoTestnet testnetOptions Conf {tempAbsPath=TmpAbsolutePath tmpAbsPath} = do
213266

214267

215268
-- Add Byron, Shelley and Alonzo genesis hashes to node configuration
216-
finalYamlConfig <- createConfigYaml (TmpAbsolutePath tmpAbsPath) $ cardanoNodeEra testnetOptions
269+
finalYamlConfig <- createConfigYaml (TmpAbsolutePath tmpAbsPath) era
217270

218271
H.evalIO $ LBS.writeFile configurationFile finalYamlConfig
219272

@@ -337,7 +390,7 @@ cardanoTestnet testnetOptions Conf {tempAbsPath=TmpAbsolutePath tmpAbsPath} = do
337390

338391
let runtime = TestnetRuntime
339392
{ configurationFile
340-
, shelleyGenesisFile = tmpAbsPath </> defaultShelleyGenesisFp
393+
, shelleyGenesisFile = tmpAbsPath </> Defaults.defaultShelleyGenesisFp
341394
, testnetMagic
342395
, poolNodes
343396
, wallets = wallets

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Cli/Babbage/LeadershipSchedule.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ hprop_leadershipSchedule = H.integrationRetryWorkspace 2 "babbage-leadership-sch
7777
{ testnetMagic
7878
, wallets
7979
, configurationFile
80-
} <- cardanoTestnet cTestnetOptions conf
80+
} <- cardanoTestnetDefault cTestnetOptions conf
8181

8282
node1sprocket <- H.headM $ poolSprockets tr
8383
execConfig <- H.mkExecConfig tempBaseAbsPath node1sprocket testnetMagic

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Cli/Babbage/StakeSnapshot.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ hprop_stakeSnapshot = H.integrationRetryWorkspace 2 "babbage-stake-snapshot" $ \
6262
TestnetRuntime
6363
{ testnetMagic
6464
, poolNodes
65-
} <- cardanoTestnet options conf
65+
} <- cardanoTestnetDefault options conf
6666

6767
poolNode1 <- H.headM poolNodes
6868
poolSprocket1 <- H.noteShow $ nodeSprocket $ poolRuntime poolNode1

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Cli/Babbage/Transaction.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ hprop_transaction = H.integrationRetryWorkspace 0 "babbage-transaction" $ \tempA
6666
{ testnetMagic
6767
, poolNodes
6868
, wallets
69-
} <- cardanoTestnet options conf
69+
} <- cardanoTestnetDefault options conf
7070

7171
poolNode1 <- H.headM poolNodes
7272
poolSprocket1 <- H.noteShow $ nodeSprocket $ poolRuntime poolNode1

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Cli/Conway/StakeSnapshot.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ hprop_stakeSnapshot = H.integrationRetryWorkspace 2 "conway-stake-snapshot" $ \t
6262
TestnetRuntime
6363
{ testnetMagic
6464
, poolNodes
65-
} <- cardanoTestnet options conf
65+
} <- cardanoTestnetDefault options conf
6666

6767
poolNode1 <- H.headM poolNodes
6868
poolSprocket1 <- H.noteShow $ nodeSprocket $ poolRuntime poolNode1

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Cli/KesPeriodInfo.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,7 @@ hprop_kes_period_info = H.integrationRetryWorkspace 2 "kes-period-info" $ \tempA
6565
, cardanoNodeEra = AnyCardanoEra era -- TODO: We should only support the latest era and the upcoming era
6666
}
6767

68-
runTime@TestnetRuntime { configurationFile, testnetMagic, wallets } <- cardanoTestnet cTestnetOptions conf
68+
runTime@TestnetRuntime { configurationFile, testnetMagic, wallets } <- cardanoTestnetDefault cTestnetOptions conf
6969
node1sprocket <- H.headM $ poolSprockets runTime
7070
execConfig <- H.mkExecConfig tempBaseAbsPath node1sprocket testnetMagic
7171

0 commit comments

Comments
 (0)