Skip to content

Commit 337539f

Browse files
committed
use 'startNode' in Shelley testcase
1 parent b2d59d2 commit 337539f

File tree

3 files changed

+31
-67
lines changed

3 files changed

+31
-67
lines changed

cardano-testnet/src/Test/Runtime.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -15,10 +15,10 @@ module Test.Runtime
1515
, PoolNode(..)
1616
, PoolNodeKeys(..)
1717
, Delegator(..)
18+
, allNodes
1819
, bftSprockets
1920
, poolSprockets
2021
, poolNodeStdout
21-
, poolNodeToTestnetNode
2222
, readNodeLoggingFormat
2323
) where
2424

@@ -99,9 +99,6 @@ data LeadershipSlot = LeadershipSlot
9999
poolNodeStdout :: PoolNode -> FilePath
100100
poolNodeStdout = nodeStdout . poolRuntime
101101

102-
poolNodeToTestnetNode :: PoolNode -> TestnetNode
103-
poolNodeToTestnetNode (PoolNode runtime _) = TestnetNode runtime
104-
105102
bftSprockets :: TestnetRuntime -> [Sprocket]
106103
bftSprockets = fmap (nodeSprocket . unTestnetNode) . bftNodes
107104

@@ -113,3 +110,6 @@ readNodeLoggingFormat = \case
113110
"json" -> Right NodeLoggingFormatAsJson
114111
"text" -> Right NodeLoggingFormatAsText
115112
s -> Left $ "Unrecognised node logging format: " <> show s <> ". Valid options: \"json\", \"text\""
113+
114+
allNodes :: TestnetRuntime -> [NodeRuntime]
115+
allNodes tr = fmap unTestnetNode (bftNodes tr) <> fmap poolRuntime (poolNodes tr)

cardano-testnet/src/Testnet/Cardano.hs

+1-6
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,6 @@ module Testnet.Cardano
1212

1313
, Era(..)
1414
, TestnetRuntime (..)
15-
, allNodes
1615
, TestnetNode (..)
1716
, PaymentKeyPair(..)
1817

@@ -42,7 +41,7 @@ import Hedgehog.Extras.Stock.Time (formatIso8601, showUTCTimeSeconds)
4241
import Ouroboros.Network.PeerSelection.LedgerPeers (UseLedgerAfter (..))
4342
import Ouroboros.Network.PeerSelection.RelayAccessPoint (RelayAccessPoint (..))
4443
import System.FilePath.Posix ((</>))
45-
import Test.Runtime (NodeLoggingFormat (..), PaymentKeyPair (..), PoolNode (PoolNode),
44+
import Test.Runtime as TR (NodeLoggingFormat (..), PaymentKeyPair (..), PoolNode (PoolNode),
4645
PoolNodeKeys (..), TestnetNode (..), TestnetRuntime (..))
4746
import Text.Read (Read)
4847
import Text.Show (Show (show))
@@ -71,7 +70,6 @@ import qualified System.Directory as IO
7170
import qualified System.Info as OS
7271
import qualified Test.Assert as H
7372
import qualified Test.Process as H
74-
import qualified Test.Runtime as TR
7573
import qualified Testnet.Conf as H
7674

7775
{- HLINT ignore "Reduce duplication" -}
@@ -123,9 +121,6 @@ defaultTestnetNodeOptions = TestnetNodeOptions
123121
{ extraNodeCliArgs = []
124122
}
125123

126-
allNodes :: TestnetRuntime -> [TestnetNode]
127-
allNodes tr = bftNodes tr <> fmap TR.poolNodeToTestnetNode (poolNodes tr)
128-
129124
ifaceAddress :: String
130125
ifaceAddress = "127.0.0.1"
131126

cardano-testnet/src/Testnet/Shelley.hs

+26-57
Original file line numberDiff line numberDiff line change
@@ -12,18 +12,17 @@ module Testnet.Shelley
1212
, hprop_testnet_pause
1313
) where
1414

15-
import Control.Monad (Monad(..), forever, forM_, void, (=<<), when)
15+
import Control.Monad
1616
import Control.Monad.IO.Class (MonadIO(liftIO))
1717
import Control.Monad.Trans.Resource (MonadResource(liftResourceT), resourceForkIO)
1818
import Data.Aeson (Value, ToJSON(toJSON))
1919
import Data.ByteString.Lazy (ByteString)
2020
import Data.Eq (Eq)
2121
import Data.Function (($), (.), flip)
22-
import Data.Functor (Functor(fmap), (<$>), (<&>))
22+
import Data.Functor
2323
import Data.Int (Int)
2424
import Data.List ((\\))
25-
import Data.Maybe (Maybe(Nothing, Just), fromJust)
26-
import Data.Ord (Ord((<=)))
25+
import Data.Maybe
2726
import Data.Semigroup (Semigroup((<>)))
2827
import Data.String (String, fromString)
2928
import Data.Time.Clock (UTCTime)
@@ -36,6 +35,9 @@ import Ouroboros.Network.PeerSelection.RelayAccessPoint (RelayAccessPo
3635
import Prelude (Bool(..), Integer, (-))
3736
import System.FilePath.Posix ((</>))
3837
import Text.Show (Show(show))
38+
import Test.Process (execCli_)
39+
import Test.Runtime hiding (allNodes)
40+
import Testnet.Utils
3941

4042
import qualified Cardano.Node.Configuration.Topology as NonP2P
4143
import qualified Cardano.Node.Configuration.TopologyP2P as P2P
@@ -58,13 +60,9 @@ import qualified Hedgehog.Extras.Test.Network as H
5860
import qualified Hedgehog.Extras.Test.Process as H
5961
import qualified System.Directory as IO
6062
import qualified System.Info as OS
61-
import qualified System.IO as IO
62-
import qualified System.Process as IO
6363
import qualified Test.Base as H
6464
import qualified Test.Process as H
6565
import qualified Testnet.Conf as H
66-
import Test.Runtime (TestnetRuntime (..))
67-
6866

6967
{- HLINT ignore "Reduce duplication" -}
7068
{- HLINT ignore "Redundant <&>" -}
@@ -189,7 +187,7 @@ shelleyTestnet testnetOptions H.Conf {..} = do
189187
liftIO $ IO.copyFile sourceAlonzoGenesisSpecFile alonzoSpecFile
190188

191189
-- Set up our template
192-
void $ H.execCli
190+
execCli_
193191
[ "genesis", "create"
194192
, "--testnet-magic", show @Int testnetMagic
195193
, "--genesis-dir", tempAbsPath
@@ -207,7 +205,7 @@ shelleyTestnet testnetOptions H.Conf {..} = do
207205
H.assertIsJsonFile $ tempAbsPath </> "genesis.spec.json"
208206

209207
-- Now generate for real
210-
void $ H.execCli
208+
execCli_
211209
[ "genesis", "create"
212210
, "--testnet-magic", show @Int testnetMagic
213211
, "--genesis-dir", tempAbsPath
@@ -221,14 +219,14 @@ shelleyTestnet testnetOptions H.Conf {..} = do
221219
-- Make the pool operator cold keys
222220
-- This was done already for the BFT nodes as part of the genesis creation
223221
forM_ poolNodes $ \n -> do
224-
void $ H.execCli
222+
execCli_
225223
[ "node", "key-gen"
226224
, "--cold-verification-key-file", tempAbsPath </> n </> "operator.vkey"
227225
, "--cold-signing-key-file", tempAbsPath </> n </> "operator.skey"
228226
, "--operational-certificate-issue-counter-file", tempAbsPath </> n </> "operator.counter"
229227
]
230228

231-
void $ H.execCli
229+
execCli_
232230
[ "node", "key-gen-VRF"
233231
, "--verification-key-file", tempAbsPath </> n </> "vrf.vkey"
234232
, "--signing-key-file", tempAbsPath </> n </> "vrf.skey"
@@ -243,13 +241,13 @@ shelleyTestnet testnetOptions H.Conf {..} = do
243241

244242
-- Make hot keys and for all nodes
245243
forM_ allNodes $ \node -> do
246-
void $ H.execCli
244+
execCli_
247245
[ "node", "key-gen-KES"
248246
, "--verification-key-file", tempAbsPath </> node </> "kes.vkey"
249247
, "--signing-key-file", tempAbsPath </> node </> "kes.skey"
250248
]
251249

252-
void $ H.execCli
250+
execCli_
253251
[ "node", "issue-op-cert"
254252
, "--kes-period", "0"
255253
, "--kes-verification-key-file", tempAbsPath </> node </> "kes.vkey"
@@ -278,21 +276,21 @@ shelleyTestnet testnetOptions H.Conf {..} = do
278276

279277
forM_ addrs $ \addr -> do
280278
-- Payment address keys
281-
void $ H.execCli
279+
execCli_
282280
[ "address", "key-gen"
283281
, "--verification-key-file", tempAbsPath </> "addresses/" <> addr <> ".vkey"
284282
, "--signing-key-file", tempAbsPath </> "addresses/" <> addr <> ".skey"
285283
]
286284

287285
-- Stake address keys
288-
void $ H.execCli
286+
execCli_
289287
[ "stake-address", "key-gen"
290288
, "--verification-key-file", tempAbsPath </> "addresses/" <> addr <> "-stake.vkey"
291289
, "--signing-key-file", tempAbsPath </> "addresses/" <> addr <> "-stake.skey"
292290
]
293291

294292
-- Payment addresses
295-
void $ H.execCli
293+
execCli_
296294
[ "address", "build"
297295
, "--payment-verification-key-file", tempAbsPath </> "addresses/" <> addr <> ".vkey"
298296
, "--stake-verification-key-file", tempAbsPath </> "addresses/" <> addr <> "-stake.vkey"
@@ -301,23 +299,23 @@ shelleyTestnet testnetOptions H.Conf {..} = do
301299
]
302300

303301
-- Stake addresses
304-
void $ H.execCli
302+
execCli_
305303
[ "stake-address", "build"
306304
, "--stake-verification-key-file", tempAbsPath </> "addresses/" <> addr <> "-stake.vkey"
307305
, "--testnet-magic", show @Int testnetMagic
308306
, "--out-file", tempAbsPath </> "addresses/" <> addr <> "-stake.addr"
309307
]
310308

311309
-- Stake addresses registration certs
312-
void $ H.execCli
310+
execCli_
313311
[ "stake-address", "registration-certificate"
314312
, "--stake-verification-key-file", tempAbsPath </> "addresses/" <> addr <> "-stake.vkey"
315313
, "--out-file", tempAbsPath </> "addresses/" <> addr <> "-stake.reg.cert"
316314
]
317315

318316
forM_ userPoolN $ \n -> do
319317
-- Stake address delegation certs
320-
void $ H.execCli
318+
execCli_
321319
[ "stake-address", "delegation-certificate"
322320
, "--stake-verification-key-file", tempAbsPath </> "addresses/user" <> n <> "-stake.vkey"
323321
, "--cold-verification-key-file", tempAbsPath </> "node-pool" <> n </> "operator.vkey"
@@ -333,7 +331,7 @@ shelleyTestnet testnetOptions H.Conf {..} = do
333331

334332
-- Next is to make the stake pool registration cert
335333
forM_ poolNodes $ \node -> do
336-
void $ H.execCli
334+
execCli_
337335
[ "stake-pool", "registration-certificate"
338336
, "--testnet-magic", show @Int testnetMagic
339337
, "--pool-pledge", "0"
@@ -367,7 +365,7 @@ shelleyTestnet testnetOptions H.Conf {..} = do
367365

368366
userNAddr <- H.readFile $ tempAbsPath </> "addresses/user" <> n <> ".addr"
369367

370-
void $ H.execCli
368+
execCli_
371369
[ "transaction", "build-raw"
372370
, "--invalid-hereafter", "1000"
373371
, "--fee", "0"
@@ -386,7 +384,7 @@ shelleyTestnet testnetOptions H.Conf {..} = do
386384
-- 3. the pool n owner key, due to the pool registration cert
387385
-- 3. the pool n operator key, due to the pool registration cert
388386

389-
void $ H.execCli
387+
execCli_
390388
[ "transaction", "sign"
391389
, "--signing-key-file", tempAbsPath </> "utxo-keys/utxo" <> n <> ".skey"
392390
, "--signing-key-file", tempAbsPath </> "addresses/user" <> n <> "-stake.skey"
@@ -409,24 +407,8 @@ shelleyTestnet testnetOptions H.Conf {..} = do
409407
<&> L.unlines . fmap (rewriteConfiguration (enableP2P testnetOptions)) . L.lines
410408
>>= H.writeFile (tempAbsPath </> "configuration.yaml")
411409

412-
forM_ allNodes $ \node -> do
413-
dbDir <- H.noteShow $ tempAbsPath </> "db/" <> node
414-
nodeStdoutFile <- H.noteTempFile logDir $ node <> ".stdout.log"
415-
nodeStderrFile <- H.noteTempFile logDir $ node <> ".stderr.log"
416-
sprocket <- H.noteShow $ Sprocket tempBaseAbsPath (socketDir </> node)
417-
418-
H.createDirectoryIfMissing dbDir
419-
H.createDirectoryIfMissing $ tempBaseAbsPath </> socketDir
420-
421-
hNodeStdout <- H.openFile nodeStdoutFile IO.WriteMode
422-
hNodeStderr <- H.openFile nodeStderrFile IO.WriteMode
423-
424-
H.diff (L.length (IO.sprocketArgumentName sprocket)) (<=) IO.maxSprocketArgumentNameLength
425-
426-
portString <- H.readFile $ tempAbsPath </> node </> "port"
427-
428-
void $ H.createProcess =<<
429-
( H.procNode
410+
allNodeRuntimes <- forM allNodes $ \node -> do
411+
runtime <- startNode socketDir tempBaseAbsPath tempAbsPath logDir node
430412
[ "run"
431413
, "--config", tempAbsPath </> "configuration.yaml"
432414
, "--topology", tempAbsPath </> node </> "topology.json"
@@ -435,20 +417,8 @@ shelleyTestnet testnetOptions H.Conf {..} = do
435417
, "--shelley-vrf-key", tempAbsPath </> node </> "vrf.skey"
436418
, "--shelley-operational-certificate" , tempAbsPath </> node </> "node.cert"
437419
, "--host-addr", ifaceAddress
438-
, "--port", portString
439-
, "--socket-path", IO.sprocketArgumentName sprocket
440-
] <&>
441-
( \cp -> cp
442-
{ IO.std_in = IO.CreatePipe
443-
, IO.std_out = IO.UseHandle hNodeStdout
444-
, IO.std_err = IO.UseHandle hNodeStderr
445-
, IO.cwd = Just tempBaseAbsPath
446-
}
447-
)
448-
)
449-
450-
when (OS.os `L.elem` ["darwin", "linux"]) $ do
451-
H.onFailure . H.noteIO_ $ IO.readProcess "lsof" ["-iTCP:" <> portString, "-sTCP:LISTEN", "-n", "-P"] ""
420+
]
421+
return $ TestnetNode runtime
452422

453423
now <- H.noteShowIO DTC.getCurrentTime
454424
deadline <- H.noteShow $ DTC.addUTCTime 90 now
@@ -469,10 +439,9 @@ shelleyTestnet testnetOptions H.Conf {..} = do
469439
{ configurationFile = alonzoSpecFile
470440
, shelleyGenesisFile = tempAbsPath </> "genesis/shelley/genesis.json"
471441
, testnetMagic
472-
-- TODO: return some useful data here !!
473442
, poolNodes = [ ]
474443
, wallets = [ ]
475-
, bftNodes = [ ]
444+
, bftNodes = allNodeRuntimes
476445
, delegators = [ ]
477446
}
478447

0 commit comments

Comments
 (0)