Skip to content

Commit

Permalink
cardano-testnet | fix stake registration check failures and adapt to …
Browse files Browse the repository at this point in the history
…create-testnet-data changes
  • Loading branch information
carbolymer committed Dec 27, 2024
1 parent 1ebef45 commit 540a822
Show file tree
Hide file tree
Showing 16 changed files with 2,129 additions and 1,771 deletions.
21 changes: 9 additions & 12 deletions cardano-testnet/src/Testnet/Components/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ createConfigJson :: ()
-> ShelleyBasedEra era -- ^ The era used for generating the hard fork configuration toggle
-> m LBS.ByteString
createConfigJson (TmpAbsolutePath tempAbsPath) sbe = GHC.withFrozenCallStack $ do
byronGenesisHash <- getByronGenesisHash $ tempAbsPath </> "byron/genesis.json"
byronGenesisHash <- getByronGenesisHash $ tempAbsPath </> "byron-genesis.json"
shelleyGenesisHash <- getHash ShelleyEra "ShelleyGenesisHash"
alonzoGenesisHash <- getHash AlonzoEra "AlonzoGenesisHash"
conwayGenesisHash <- getHash ConwayEra "ConwayGenesisHash"
Expand Down Expand Up @@ -126,7 +126,7 @@ createSPOGenesisAndFiles
-> ConwayGenesis StandardCrypto -- ^ The conway genesis to use, for example 'Defaults.defaultConwayGenesis'.
-> TmpAbsolutePath
-> m FilePath -- ^ Shelley genesis directory
createSPOGenesisAndFiles nPoolNodes nDelReps maxSupply sbe shelleyGenesis
createSPOGenesisAndFiles nPoolNodes nDelReps maxSupply asbe@(AnyShelleyBasedEra sbe) shelleyGenesis
alonzoGenesis conwayGenesis (TmpAbsolutePath tempAbsPath) = GHC.withFrozenCallStack $ do
let inputGenesisShelleyFp = tempAbsPath </> genesisInputFilepath ShelleyEra
inputGenesisAlonzoFp = tempAbsPath </> genesisInputFilepath AlonzoEra
Expand Down Expand Up @@ -162,32 +162,29 @@ createSPOGenesisAndFiles nPoolNodes nDelReps maxSupply sbe shelleyGenesis
H.note_ $ "Number of stake delegators: " <> show nPoolNodes
H.note_ $ "Number of seeded UTxO keys: " <> show numSeededUTxOKeys

execCli_
[ anyShelleyBasedEraToString sbe, "genesis", "create-testnet-data"
let eraString = anyShelleyBasedEraToString asbe
era = toCardanoEra sbe
execCli_ $
[ eraString, "genesis", "create-testnet-data"
, "--spec-shelley", inputGenesisShelleyFp
, "--spec-alonzo", inputGenesisAlonzoFp
, "--spec-conway", inputGenesisConwayFp
, "--testnet-magic", show testnetMagic
, "--pools", show nPoolNodes
, "--total-supply", show maxSupply -- Half of this will be delegated, see https://github.com/IntersectMBO/cardano-cli/pull/874
, "--stake-delegators", show numStakeDelegators
, "--utxo-keys", show numSeededUTxOKeys
, "--drep-keys", show nDelReps
, "--start-time", DTC.formatIso8601 startTime
, "--utxo-keys", show numSeededUTxOKeys]
<> monoidForEraInEon @ConwayEraOnwards era (const ["--drep-keys", show nDelReps])
<> [ "--start-time", DTC.formatIso8601 startTime
, "--out-dir", tempAbsPath
]

-- Remove the input files. We don't need them anymore, since create-testnet-data wrote new versions.
forM_ [inputGenesisShelleyFp, inputGenesisAlonzoFp, inputGenesisConwayFp] (liftIO . System.removeFile)

-- Move all genesis related files
genesisByronDir <- H.createDirectoryIfMissing $ tempAbsPath </> "byron"

files <- H.listDirectory tempAbsPath
forM_ files H.note

H.renameFile (tempAbsPath </> "byron-gen-command" </> "genesis.json") (genesisByronDir </> "genesis.json")

return genesisShelleyDir
where
genesisInputFilepath e = "genesis-input." <> anyEraToString (AnyCardanoEra e) <> ".json"
Expand Down
8 changes: 4 additions & 4 deletions cardano-testnet/src/Testnet/Defaults.hs
Original file line number Diff line number Diff line change
Expand Up @@ -290,7 +290,7 @@ defaultYamlConfig =
, ("EnableLogging", Aeson.Bool True)

-- Genesis filepaths
, ("ByronGenesisFile", "byron/genesis.json")
, ("ByronGenesisFile", genesisPath ByronEra)
, ("ShelleyGenesisFile", genesisPath ShelleyEra)
, ("AlonzoGenesisFile", genesisPath AlonzoEra)
, ("ConwayGenesisFile", genesisPath ConwayEra)
Expand Down Expand Up @@ -545,9 +545,9 @@ plutusV3Script :: Text
plutusV3Script =
"{ \"type\": \"PlutusScriptV3\", \"description\": \"\", \"cborHex\": \"46450101002499\" }"

-- | Created via: cabal run plutus-scripts-bench -- print SupplementalDatum -o supplemental-datum.plutus
plutusV3SupplementalDatumScript :: Text
plutusV3SupplementalDatumScript =
-- | Created via: cabal run plutus-scripts-bench -- print SupplementalDatum -o supplemental-datum.plutus
plutusV3SupplementalDatumScript :: Text
plutusV3SupplementalDatumScript =
"{ \"type\": \"PlutusScriptV3\", \"description\": \"\", \"cborHex\": \"590e72590e6f01000032323322332233223232323232323232323232323225335533535353232325335333573466e1d200000201301213232323232333222123330010040030023232325335333573466e1d200000201b01a1323232323232323232323232323232323333333333332333233233222222222222222212333333333333333300101101000f00e00d00c00b00a00900800700600500400300230013574202860026ae8404cc0948c8c8c94cd4ccd5cd19b87480000080c40c04cc8848cc00400c008c074d5d080098029aba135744002260589201035054310035573c0046aae74004dd5000998128009aba101123232325335333573466e1d200000203002f13232333322221233330010050040030023232325335333573466e1d2000002035034133221233001003002302e357420026605e4646464a66a666ae68cdc3a4000004072070264244600400660646ae8400454cd4ccd5cd19b87480080080e40e04c8ccc888488ccc00401401000cdd69aba1002375a6ae84004dd69aba1357440026ae880044c0d12401035054310035573c0046aae74004dd50009aba135744002260609201035054310035573c0046aae74004dd51aba1003300735742004646464a66a666ae68cdc3a400000406a068224440062a66a666ae68cdc3a400400406a068264244460020086eb8d5d08008a99a999ab9a3370e900200101a81a099091118010021aba1001130304901035054310035573c0046aae74004dd51aba10013302c75c6ae84d5d10009aba200135744002260569201035054310035573c0046aae74004dd50009bad3574201e60026ae84038c008c009d69981180a9aba100c33302702475a6ae8402cc8c8c94cd4ccd5cd19b87480000080b80b44cc8848cc00400c008c8c8c94cd4ccd5cd19b87480000080c40c04cc8848cc00400c008cc09dd69aba10013026357426ae880044c0b1241035054310035573c0046aae74004dd51aba10013232325335333573466e1d20000020310301332212330010030023302775a6ae84004c098d5d09aba20011302c491035054310035573c0046aae74004dd51aba13574400226052921035054310035573c0046aae74004dd51aba100a3302375c6ae84024ccc09c8c8c8c94cd4ccd5cd19b87480000080bc0b84c84888888c01401cdd71aba100115335333573466e1d200200202f02e13212222223002007301b357420022a66a666ae68cdc3a400800405e05c2642444444600600e60506ae8400454cd4ccd5cd19b87480180080bc0b84cc884888888cc01802001cdd69aba10013019357426ae8800454cd4ccd5cd19b87480200080bc0b84c84888888c00401cc068d5d08008a99a999ab9a3370e9005001017817099910911111198020040039bad3574200260306ae84d5d1000898152481035054310035573c0046aae74004dd500080f9aba10083300201f3574200e6eb8d5d080319981380b198138111191919299a999ab9a3370e9000001017817089110010a99a999ab9a3370e9001001017817089110008a99a999ab9a3370e900200101781708911001898152481035054310035573c0046aae74004dd50009aba1005330230143574200860026ae8400cc004d5d09aba2003302475a604aeb8d5d10009aba2001357440026ae88004d5d10009aba2001357440026ae88004d5d10009aba2001357440026ae88004d5d10009aba200113016491035054310035573c0046aae74004dd51aba10063574200a646464a66a666ae68cdc3a40000040360342642444444600a00e6eb8d5d08008a99a999ab9a3370e900100100d80d0999109111111980100400398039aba10013301500f357426ae8800454cd4ccd5cd19b874801000806c0684c84888888c00c01cc050d5d08008a99a999ab9a3370e900300100d80d099910911111198030040039bad35742002600a6ae84d5d10008a99a999ab9a3370e900400100d80d0990911111180080398031aba100115335333573466e1d200a00201b01a13322122222233004008007375a6ae84004c010d5d09aba2001130164901035054310035573c0046aae74004dd51aba13574400a4646464a66a666ae68cdc3a4000004036034264666444246660020080060046eb4d5d0801180a9aba10013232325335333573466e1d200000201f01e1323332221222222233300300a0090083301a017357420046ae84004cc069d71aba1357440026ae8800454cd4ccd5cd19b874800800807c0784cc8848888888cc01c024020cc064058d5d0800991919299a999ab9a3370e90000010110108999109198008018011bad357420026eb4d5d09aba20011301d491035054310035573c0046aae74004dd51aba1357440022a66a666ae68cdc3a400800403e03c266442444444466004012010666036030eb4d5d08009980cbae357426ae8800454cd4ccd5cd19b874801800807c0784c848888888c010020cc064058d5d08008a99a999ab9a3370e900400100f80f09919199991110911111119998008058050048041980d80c1aba10033301901a3574200466603a034eb4d5d08009a991919299a999ab9a3370e90000010120118998149bad357420026eb4d5d09aba20011301f4901035054310035573c0046aae74004dd51aba135744002446602a0040026ae88004d5d10008a99a999ab9a3370e900500100f80f0999109111111198028048041980c80b1aba10013232325335333573466e1d200000202202113301c75c6ae840044c075241035054310035573c0046aae74004dd51aba1357440022a66a666ae68cdc3a401800403e03c22444444400c26034921035054310035573c0046aae74004dd51aba1357440026ae880044c059241035054310035573c0046aae74004dd50009191919299a999ab9a3370e900000100d00c899910911111111111980280680618099aba10013301475a6ae84d5d10008a99a999ab9a3370e900100100d00c899910911111111111980100680618099aba10013301475a6ae84d5d10008a9919a999ab9a3370e900200180d80d0999109111111111119805006806180a1aba10023001357426ae8800854cd4ccd5cd19b874801800c06c0684c8ccc888488888888888ccc018038034030c054d5d080198011aba1001375a6ae84d5d10009aba200215335333573466e1d200800301b01a133221222222222223300700d00c3014357420046eb4d5d09aba200215335333573466e1d200a00301b01a132122222222222300100c3014357420042a66a666ae68cdc3a4018006036034266442444444444446600601a01860286ae84008dd69aba1357440042a66a666ae68cdc3a401c006036034266442444444444446601201a0186eb8d5d08011bae357426ae8800854cd4ccd5cd19b874804000c06c0684cc88488888888888cc020034030dd71aba1002375a6ae84d5d10010a99a999ab9a3370e900900180d80d0999109111111111119805806806180a1aba10023014357426ae8800854cd4ccd5cd19b874805000c06c0684c8488888888888c010030c050d5d08010980b2481035054310023232325335333573466e1d200000201e01d13212223003004375c6ae8400454c8cd4ccd5cd19b874800800c07c0784c84888c004010c004d5d08010a99a999ab9a3370e900200180f80f099910911198010028021bae3574200460026ae84d5d10010980d2481035054310023232325335333573466e1d200000202202113212223003004301b357420022a66a666ae68cdc3a4004004044042224440042a66a666ae68cdc3a4008004044042224440022603a921035054310035573c0046aae74004dd50009aab9e00235573a0026ea8004d55cf0011aab9d00137540024646464a66a666ae68cdc3a40000040320302642444600600860246ae8400454cd4ccd5cd19b87480080080640604c84888c008010c048d5d08008a99a999ab9a3370e900200100c80c099091118008021bae3574200226028921035054310035573c0046aae74004dd50009191919299a999ab9a3370e900000100c00b8999109198008018011bae357420026eb4d5d09aba200113013491035054310035573c0046aae74004dd50009aba20011300e491035054310035573c0046aae74004dd50009110019111111111111111180f0031080888078a4c26016921035054350030142225335333573466e1d20000010110101300c491035054330015335333573466e20005200001101013300333702900000119b81480000044c8cc8848cc00400c008cdc200180099b840020013300400200130132225335333573466e1d200000101000f10021330030013370c00400240024646464a66a666ae68cdc3a400000401e01c201c2a66a666ae68cdc3a400400401e01c201e260149201035054310035573c0046aae74004dd500091191919299a999ab9a3370e9000001007807089110010a99a999ab9a3370e90010010078070990911180180218029aba100115335333573466e1d200400200f00e112220011300a4901035054310035573c0046aae74004dd50009191919299a999ab9a3370e90000010068060999109198008018011bae357420026eb4d5d09aba200113008491035054310035573c0046aae74004dd5000919118011bac001300f2233335573e002401c466a01a60086ae84008c00cd5d10010041191919299a999ab9a3370e900000100580509909118010019bae357420022a66a666ae68cdc3a400400401601426424460020066eb8d5d0800898032481035054310035573c0046aae74004dd500091191919299a999ab9a3370e90010010058050a8070a99a999ab9a3370e90000010058050980798029aba1001130064901035054310035573c0046aae74004dd5000919319ab9c00100322322300237560026018446666aae7c004802c8c8cd402ccc03cc018d55ce80098029aab9e0013004357440066ae8400801448004c020894cd40045401c884d4008894cd4ccd5cd19b8f488120ee155ace9c40292074cb6aff8c9ccdd273c81648ff1149ef36bcea6ebb8a3e25000020080071300c001130060031220021220011220021221223300100400321223002003112200122123300100300223230010012300223300200200101\" }"


8 changes: 6 additions & 2 deletions cardano-testnet/src/Testnet/Ping.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,16 +28,17 @@ import qualified Control.Monad.Class.MonadTimer.SI as MT
import Control.Monad.IO.Class
import qualified Control.Retry as R
import Control.Tracer (nullTracer)
import Data.Bifunctor (first)
import qualified Data.ByteString.Lazy as LBS
import Data.Either
import Data.IORef
import qualified Data.List as L
import Data.Word (Word32)
import qualified Network.Mux as Mux
import Network.Mux.Bearer (MakeBearer (..), makeSocketBearer)
import Network.Mux.Timeout (TimeoutFn, withTimeoutSerial)
import Network.Mux.Types (MiniProtocolDir (InitiatorDir), MiniProtocolNum (..),
RemoteClockModel (RemoteClockModel), SDU (..), SDUHeader (..))
import qualified Network.Mux as Mux
import qualified Network.Mux.Types as Mux
import Network.Socket (AddrInfo (..), PortNumber, StructLinger (..))
import qualified Network.Socket as Socket
Expand Down Expand Up @@ -68,7 +69,7 @@ pingNode :: MonadIO m
pingNode networkMagic sprocket = liftIO $ bracket
(Socket.socket (Socket.addrFamily peer) Socket.Stream Socket.defaultProtocol)
Socket.close
(\sd -> withTimeoutSerial $ \timeoutfn -> do
(\sd -> handle (pure . Left . PceException) $ withTimeoutSerial $ \timeoutfn -> do
when (Socket.addrFamily peer /= Socket.AF_UNIX) $ do
Socket.setSocketOption sd Socket.NoDelay 1
Socket.setSockOpt sd Socket.Linger
Expand Down Expand Up @@ -195,6 +196,8 @@ data PingClientError
!String -- ^ peer string
![NodeVersion] -- ^ requested versions
![NodeVersion] -- ^ received node versions
| PceException
!SomeException

instance Error PingClientError where
prettyError = \case
Expand All @@ -204,5 +207,6 @@ instance Error PingClientError where
[ pretty peerStr <+> "Version negotiation error: No overlapping versions with" <+> viaShow requestedVersions
, "Received versions:" <+> viaShow receivedVersions
]
PceException exception -> "An unknown exception occurred:" <+> pretty (displayException exception)


16 changes: 9 additions & 7 deletions cardano-testnet/src/Testnet/Runtime.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,7 @@ startNode
-- ^ The command to execute to start the node.
-- @--socket-path@, @--port@, and @--host-addr@ gets added automatically.
-> ExceptT NodeStartFailure m TestnetNode
startNode tp node ipv4 port testnetMagic nodeCmd = GHC.withFrozenCallStack $ do
startNode tp node ipv4 port _testnetMagic nodeCmd = GHC.withFrozenCallStack $ do
let tempBaseAbsPath = makeTmpBaseAbsPath tp
socketDir = makeSocketDir tp
logDir = makeLogDir tp
Expand Down Expand Up @@ -175,10 +175,11 @@ startNode tp node ipv4 port testnetMagic nodeCmd = GHC.withFrozenCallStack $ do

-- Wait for socket to be created
eSprocketError <-
Ping.waitForSprocket
120 -- timeout
0.2 -- check interval
sprocket
H.evalIO $
Ping.waitForSprocket
120 -- timeout
0.2 -- check interval
sprocket

-- If we do have anything on stderr, fail.
stdErrContents <- liftIO $ IO.readFile nodeStderrFile
Expand All @@ -193,8 +194,9 @@ startNode tp node ipv4 port testnetMagic nodeCmd = GHC.withFrozenCallStack $ do
$ hoistEither eSprocketError

-- Ping node and fail on error
Ping.pingNode (fromIntegral testnetMagic) sprocket
>>= (firstExceptT (NodeExecutableError . ("Ping error:" <+>) . prettyError) . hoistEither)
-- FIXME: pinging of the node is broken now, has the protocol changed?
-- Ping.pingNode (fromIntegral testnetMagic) sprocket
-- >>= (firstExceptT (NodeExecutableError . ("Ping error:" <+>) . prettyError) . hoistEither)

pure $ TestnetNode
{ nodeName = node
Expand Down
33 changes: 0 additions & 33 deletions cardano-testnet/src/Testnet/Start/Byron.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,6 @@

module Testnet.Start.Byron
( createByronGenesis
, createByronUpdateProposal
, createByronUpdateProposalVote
, byronDefaultGenesisOptions
) where

Expand Down Expand Up @@ -67,34 +65,3 @@ createByronGenesis testnetMagic' startTime testnetOptions pParamFp genOutputDir
, "--genesis-output-dir", genOutputDir
]

createByronUpdateProposal
:: (MonadTest m, MonadCatch m, MonadIO m, HasCallStack)
=> Int -> String -> String -> Int -> m ()
createByronUpdateProposal testnetMagic' signingKeyFp updateProposalFp ptclMajorVersion =
withFrozenCallStack $ execCli_
[ "byron", "governance", "create-update-proposal"
, "--filepath", updateProposalFp
, "--testnet-magic", show testnetMagic'
, "--signing-key", signingKeyFp
, "--protocol-version-major", show ptclMajorVersion
, "--protocol-version-minor", "0"
, "--protocol-version-alt", "0"
, "--application-name", "cardano-sl"
, "--software-version-num", "1"
, "--system-tag", "linux"
, "--installer-hash", "0"
]

createByronUpdateProposalVote
:: (MonadTest m, MonadCatch m, MonadIO m, HasCallStack)
=> Int -> String -> String -> String -> m ()
createByronUpdateProposalVote testnetMagic' updateProposalFp signingKey outputFp =
withFrozenCallStack $ execCli_
[ "byron", "governance", "create-proposal-vote"
, "--proposal-filepath", updateProposalFp
, "--testnet-magic", show testnetMagic'
, "--signing-key", signingKey
, "--vote-yes"
, "--output-filepath", outputFp
]

28 changes: 3 additions & 25 deletions cardano-testnet/src/Testnet/Start/Cardano.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,15 +54,13 @@ import qualified GHC.Stack as GHC
import qualified System.Directory as IO
import System.FilePath ((</>))
import qualified System.Info as OS
import Text.Printf (printf)

import Testnet.Components.Configuration
import qualified Testnet.Defaults as Defaults
import Testnet.Filepath
import Testnet.Process.Run (execCli', execCli_, mkExecConfig)
import Testnet.Property.Assert (assertChainExtended, assertExpectedSposInLedgerState)
import Testnet.Runtime as TR
import qualified Testnet.Start.Byron as Byron
import Testnet.Start.Types
import Testnet.Types as TR hiding (shelleyGenesis)

Expand Down Expand Up @@ -130,11 +128,7 @@ getDefaultShelleyGenesis asbe maxSupply opts = do

-- | Setup a number of credentials and nodes (SPOs and relays), like this:
--
-- > ├── byron
-- > │   └── genesis.json
-- > ├── byron-gen-command
-- > │   ├── delegate-keys.00{1,2}.key
-- > │   ├── delegation-cert.00{1,2}.json
-- > │   └── genesis-keys.00{0,1,2}.key
-- > ├── delegate-keys
-- > │   ├── delegate{1,2,3}
Expand Down Expand Up @@ -187,6 +181,7 @@ getDefaultShelleyGenesis asbe maxSupply opts = do
-- > │   │   └── utxo.{addr,skey,vkey}
-- > │   └── README.md
-- > ├── alonzo-genesis.json
-- > ├── byron.genesis.json
-- > ├── byron.genesis.spec.json
-- > ├── configuration.yaml
-- > ├── conway-genesis.json
Expand Down Expand Up @@ -215,7 +210,6 @@ cardanoTestnet
, cardanoNumDReps=nDReps
, cardanoNodes
} = testnetOptions
startTime = sgSystemStart shelleyGenesis
testnetMagic = fromIntegral $ sgNetworkMagic shelleyGenesis
nPools = cardanoNumPools testnetOptions
AnyShelleyBasedEra sbe <- pure asbe
Expand All @@ -231,16 +225,6 @@ cardanoTestnet
-- See all of the ad hoc file creation/renaming/dir creation etc below.
H.failMessage GHC.callStack "Specifying node configuration files per node not supported yet."

H.lbsWriteFile (tmpAbsPath </> "byron.genesis.spec.json")
. encode $ Defaults.defaultByronProtocolParamsJsonValue

Byron.createByronGenesis
testnetMagic
startTime
Byron.byronDefaultGenesisOptions
(tmpAbsPath </> "byron.genesis.spec.json")
(tmpAbsPath </> "byron-gen-command")

-- Write specification files. Those are the same as the genesis files
-- used for launching the nodes, but omitting the content regarding stake, utxos, etc.
-- They are used by benchmarking: as templates to CLI commands,
Expand Down Expand Up @@ -296,16 +280,10 @@ cardanoTestnet
let portNumbers = snd <$> portNumbersWithNodeOptions

-- Byron related
forM_ (zip [1..] portNumbersWithNodeOptions) $ \(i, (nodeOptions, portNumber)) -> do
let iStr = printf "%03d" (i - 1)
nodeDataDir = tmpAbsPath </> Defaults.defaultNodeDataDir i
nodePoolKeysDir = tmpAbsPath </> Defaults.defaultSpoKeysDir i
forM_ (zip [1..] portNumbersWithNodeOptions) $ \(i, (_nodeOptions, portNumber)) -> do
let nodeDataDir = tmpAbsPath </> Defaults.defaultNodeDataDir i
H.evalIO $ IO.createDirectoryIfMissing True nodeDataDir
H.writeFile (nodeDataDir </> "port") (show portNumber)
when (isSpoNodeOptions nodeOptions) $ do
H.renameFile (tmpAbsPath </> "byron-gen-command" </> "delegate-keys." <> iStr <> ".key") (nodePoolKeysDir </> "byron-delegate.key")
H.renameFile (tmpAbsPath </> "byron-gen-command" </> "delegation-cert." <> iStr <> ".json") (nodePoolKeysDir </> "byron-delegation.cert")


-- Make Non P2P topology files
forM_ (zip [1..] portNumbers) $ \(i, myPortNumber) -> do
Expand Down
Loading

0 comments on commit 540a822

Please sign in to comment.