@@ -16,13 +16,11 @@ module Testnet.Start.Cardano
1616 , PaymentKeyPair (.. )
1717
1818 , cardanoTestnet
19-
19+ , cardanoTestnetDefault
2020 ) where
2121
2222
2323import Control.Monad
24- import qualified Control.Monad.Class.MonadTimer.SI as MT
25- import Control.Monad.IO.Class
2624import Control.Monad.Trans.Class (lift )
2725import Control.Monad.Trans.Except (runExceptT )
2826import Data.Aeson
@@ -43,14 +41,25 @@ import qualified Hedgehog.Extras.Stock.OS as OS
4341import qualified Hedgehog.Extras.Test.Base as H
4442import 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 )
4656import Testnet.Components.Configuration
47- import Testnet.Defaults
4857import Testnet.Filepath
4958import qualified Testnet.Process.Run as H
5059import Testnet.Process.Run
5160import qualified Testnet.Property.Assert as H
5261import Testnet.Property.Checks
53- import Testnet.Runtime
62+ import Testnet.Runtime as TR hiding ( shelleyGenesis )
5463import qualified Testnet.Start.Byron as Byron
5564import Testnet.Start.Types
5665
@@ -63,10 +72,11 @@ import Testnet.Start.Types
6372-- a valid node cluster.
6473testnetMinimumConfigurationRequirements :: CardanoTestnetOptions -> H. Integration ()
6574testnetMinimumConfigurationRequirements 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
7181data ForkPoint
7282 = AtVersion Int
@@ -79,6 +89,19 @@ data ForkPoint
7989startTimeOffsetSeconds :: DTC. NominalDiffTime
8090startTimeOffsetSeconds = 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
0 commit comments