diff --git a/cardano-node-chairman/test/Spec/Chairman/Cardano.hs b/cardano-node-chairman/test/Spec/Chairman/Cardano.hs index 533d30d98f8..f72a029052e 100644 --- a/cardano-node-chairman/test/Spec/Chairman/Cardano.hs +++ b/cardano-node-chairman/test/Spec/Chairman/Cardano.hs @@ -23,7 +23,7 @@ hprop_chairman :: H.Property hprop_chairman = H.integrationRetryWorkspace 2 "cardano-chairman" $ \tempAbsPath' -> do base <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase configurationTemplate <- H.noteShow $ base "configuration/defaults/byron-mainnet/configuration.yaml" - conf <- H.mkConf (H.ProjectBase base) (Just $ H.YamlFilePath configurationTemplate) tempAbsPath' Nothing + conf <- H.mkConf (Just $ H.YamlFilePath configurationTemplate) tempAbsPath' Nothing allNodes <- fmap H.nodeName . H.allNodes <$> H.testnet (H.CardanoOnlyTestnetOptions H.cardanoDefaultTestnetOptions) conf diff --git a/cardano-node-chairman/testnet/Testnet/Run.hs b/cardano-node-chairman/testnet/Testnet/Run.hs index a98063cfe21..e47d916bacc 100644 --- a/cardano-node-chairman/testnet/Testnet/Run.hs +++ b/cardano-node-chairman/testnet/Testnet/Run.hs @@ -27,7 +27,7 @@ testnetProperty :: Maybe Int -> (H.Conf -> H.Integration ()) -> H.Property testnetProperty maybeTestnetMagic tn = H.integrationRetryWorkspace 2 "testnet-chairman" $ \tempAbsPath' -> do base <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase configurationTemplate <- H.noteShow $ base "configuration/defaults/byron-mainnet/configuration.yaml" - conf <- H.mkConf (H.ProjectBase base) (Just $ H.YamlFilePath configurationTemplate) tempAbsPath' maybeTestnetMagic + conf <- H.mkConf (Just $ H.YamlFilePath configurationTemplate) tempAbsPath' maybeTestnetMagic -- Fork a thread to keep alive indefinitely any resources allocated by testnet. void . liftResourceT . resourceForkIO . forever . liftIO $ IO.threadDelay 10000000 diff --git a/cardano-testnet/cardano-testnet.cabal b/cardano-testnet/cardano-testnet.cabal index 0a644b42542..3cf6d8e41f9 100644 --- a/cardano-testnet/cardano-testnet.cabal +++ b/cardano-testnet/cardano-testnet.cabal @@ -38,6 +38,9 @@ library , cardano-cli , cardano-crypto-class , cardano-crypto-wrapper + , cardano-ledger-alonzo + , cardano-ledger-conway + , cardano-ledger-core , cardano-git-rev , cardano-ledger-core , cardano-ledger-byron @@ -72,7 +75,10 @@ library exposed-modules: Cardano.Testnet Testnet.Babbage Testnet.Byron + Testnet.Commands.Genesis Testnet.Options + Testnet.Topology + Testnet.Utils Testnet.Util.Assert Testnet.Util.Base Testnet.Util.Cli @@ -90,11 +96,9 @@ library Testnet Testnet.Cardano Testnet.Conf - Testnet.Commands.Genesis Testnet.Commands.Governance Testnet.Run Testnet.Shelley - Testnet.Utils Paths_cardano_testnet autogen-modules: Paths_cardano_testnet diff --git a/cardano-testnet/src/Cardano/Testnet.hs b/cardano-testnet/src/Cardano/Testnet.hs index 8146de6f5bd..502f3d47645 100644 --- a/cardano-testnet/src/Cardano/Testnet.hs +++ b/cardano-testnet/src/Cardano/Testnet.hs @@ -38,7 +38,7 @@ module Cardano.Testnet ( import Testnet import Testnet.Cardano -import Testnet.Conf hiding (base) +import Testnet.Conf import Testnet.Options import Testnet.Shelley as Shelley import Testnet.Utils (waitUntilEpoch) diff --git a/cardano-testnet/src/Testnet/Babbage.hs b/cardano-testnet/src/Testnet/Babbage.hs index 2d27f9a8918..8bca25b6585 100644 --- a/cardano-testnet/src/Testnet/Babbage.hs +++ b/cardano-testnet/src/Testnet/Babbage.hs @@ -18,6 +18,7 @@ import Prelude import Control.Monad import Data.Aeson (Value (..), encode, object, toJSON, (.=)) +import Data.Bifunctor import qualified Data.ByteString.Lazy as LBS import qualified Data.HashMap.Lazy as HM import qualified Data.List as L @@ -54,7 +55,7 @@ startTimeOffsetSeconds = if OS.isWin32 then 90 else 15 babbageTestnet :: BabbageTestnetOptions -> H.Conf -> H.Integration TestnetRuntime babbageTestnet testnetOptions H.Conf {..} = do H.lbsWriteFile (tempAbsPath "byron.genesis.spec.json") - . encode $ defaultByronGenesisJsonValue + . encode $ defaultByronProtocolParamsJsonValue void $ H.note OS.os currentTime <- H.noteShowIO DTC.getCurrentTime @@ -72,13 +73,12 @@ babbageTestnet testnetOptions H.Conf {..} = do -- are deprecated, we must use the "create-staked" cli command to create -- SPOs in the ShelleyGenesis - alonzoBabbageTestGenesisJsonSourceFile <- H.noteShow $ base "scripts/babbage/alonzo-babbage-test-genesis.json" alonzoBabbageTestGenesisJsonTargetFile <- H.noteShow $ tempAbsPath "genesis.alonzo.spec.json" - H.copyFile alonzoBabbageTestGenesisJsonSourceFile alonzoBabbageTestGenesisJsonTargetFile + gen <- H.evalEither $ first displayError defaultAlonzoGenesis + H.evalIO $ LBS.writeFile alonzoBabbageTestGenesisJsonTargetFile $ encode gen - conwayBabbageTestGenesisJsonSourceFile <- H.noteShow $ base "scripts/babbage/conway-babbage-test-genesis.json" conwayBabbageTestGenesisJsonTargetFile <- H.noteShow $ tempAbsPath "genesis.conway.spec.json" - H.copyFile conwayBabbageTestGenesisJsonSourceFile conwayBabbageTestGenesisJsonTargetFile + H.evalIO $ LBS.writeFile conwayBabbageTestGenesisJsonTargetFile $ encode defaultConwayGenesis configurationFile <- H.noteShow $ tempAbsPath "configuration.yaml" diff --git a/cardano-testnet/src/Testnet/Byron.hs b/cardano-testnet/src/Testnet/Byron.hs index 2f9b3b5ac00..55e10f44b53 100644 --- a/cardano-testnet/src/Testnet/Byron.hs +++ b/cardano-testnet/src/Testnet/Byron.hs @@ -1,5 +1,4 @@ {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TypeApplications #-} {-# OPTIONS_GHC -Wno-unused-local-binds -Wno-unused-matches #-} @@ -14,6 +13,7 @@ module Testnet.Byron import Control.Monad (forM_, void, when) import Data.Aeson (Value) import Data.ByteString.Lazy (ByteString) +import qualified Data.ByteString.Lazy as LBS import Data.Functor ((<&>)) import Hedgehog.Extras.Stock.Aeson (rewriteObject) import Hedgehog.Extras.Stock.IO.Network.Sprocket (Sprocket (..)) @@ -22,12 +22,13 @@ import Ouroboros.Network.PeerSelection.LedgerPeers (UseLedgerAfter (.. import Ouroboros.Network.PeerSelection.RelayAccessPoint (RelayAccessPoint (..)) import System.FilePath.Posix (()) +import Cardano.Api hiding (Value) + import qualified Cardano.Node.Configuration.Topology as NonP2P import qualified Cardano.Node.Configuration.TopologyP2P as P2P import qualified Data.Aeson as J import qualified Data.HashMap.Lazy as HM import qualified Data.List as L -import qualified Data.Text as T import qualified Data.Time.Clock as DTC import qualified Hedgehog as H import qualified Hedgehog.Extras.Stock.IO.File as IO @@ -41,8 +42,11 @@ import qualified Hedgehog.Extras.Test.Process as H import qualified System.Info as OS import qualified System.IO as IO import qualified System.Process as IO +import Testnet.Commands.Genesis import qualified Testnet.Conf as H +import Testnet.Options hiding (defaultTestnetOptions) import qualified Testnet.Util.Process as H +import Testnet.Utils {- HLINT ignore "Reduce duplication" -} {- HLINT ignore "Redundant <&>" -} @@ -68,20 +72,6 @@ defaultTestnetOptions = TestnetOptions , enableP2P = False } -replaceNodeLog :: Int -> String -> String -replaceNodeLog n s = T.unpack (T.replace "logs/node-0.log" replacement (T.pack s)) - where replacement = T.pack ("logs/node-" <> show @Int n <> ".log") - --- TODO: We need to refactor this to directly check the parsed configuration --- and fail with a suitable error message. --- | Rewrite a line in the configuration file -rewriteConfiguration :: Bool -> Int -> String -> String -rewriteConfiguration _ _ "TraceBlockchainTime: False" = "TraceBlockchainTime: True" -rewriteConfiguration _ n s | "logs/node-0.log" `L.isInfixOf` s = replaceNodeLog n s -rewriteConfiguration True _ "EnableP2P: False" = "EnableP2P: True" -rewriteConfiguration False _ "EnableP2P: True" = "EnableP2P: False" -rewriteConfiguration _ _ s = s - rewriteParams :: TestnetOptions -> Value -> Value rewriteParams testnetOptions = rewriteObject $ HM.insert "slotDuration" (J.toJSON @String (show @Int (slotDuration testnetOptions))) @@ -89,21 +79,21 @@ rewriteParams testnetOptions = rewriteObject mkTopologyConfig :: Int -> Int -> [Int] -> Bool -- ^ if true use p2p topology configuration -> ByteString -mkTopologyConfig i numBftNodes allPorts False = J.encode topologyNonP2P +mkTopologyConfig i numBftNodes' allPorts False = J.encode topologyNonP2P where topologyNonP2P :: NonP2P.NetworkTopology topologyNonP2P = NonP2P.RealNodeTopology - $ flip fmap ([0 .. numBftNodes - 1] L.\\ [i]) + $ flip fmap ([0 .. numBftNodes' - 1] L.\\ [i]) $ \j -> NonP2P.RemoteAddress "127.0.0.1" (fromIntegral $ allPorts L.!! j) 1 -mkTopologyConfig i numBftNodes allPorts True = J.encode topologyP2P +mkTopologyConfig i numBftNodes' allPorts True = J.encode topologyP2P where rootConfig :: P2P.RootConfig rootConfig = P2P.RootConfig - (flip fmap ([0 .. numBftNodes - 1] L.\\ [i]) + (flip fmap ([0 .. numBftNodes' - 1] L.\\ [i]) $ \j -> RelayAccessAddress "127.0.0.1" (fromIntegral $ allPorts L.!! j) ) @@ -113,7 +103,7 @@ mkTopologyConfig i numBftNodes allPorts True = J.encode topologyP2P localRootPeerGroups = P2P.LocalRootPeersGroups [ P2P.LocalRootPeersGroup rootConfig - (numBftNodes - 1) + (numBftNodes' - 1) ] topologyP2P :: P2P.NetworkTopology @@ -125,16 +115,22 @@ mkTopologyConfig i numBftNodes allPorts True = J.encode topologyP2P testnet :: TestnetOptions -> H.Conf -> H.Integration [String] -testnet testnetOptions H.Conf {..} = do +testnet testnetOptions conf = do void $ H.note OS.os - baseConfig <- H.noteShow $ base "configuration/chairman/defaults/simpleview" + let tNetMagic = H.testnetMagic conf currentTime <- H.noteShowIO DTC.getCurrentTime startTime <- H.noteShow $ DTC.addUTCTime 15 currentTime -- 15 seconds into the future allPorts <- H.noteShowIO $ IO.allocateRandomPorts (numBftNodes testnetOptions) + let tempAbsPath' = H.tempAbsPath conf + sockDir = H.socketDir conf + tempBaseAbsPath' = H.tempBaseAbsPath conf + + H.lbsWriteFile (tempAbsPath' "byron.genesis.spec.json") + . J.encode $ defaultByronProtocolParamsJsonValue H.copyRewriteJsonFile - (base "scripts/protocol-params.json") - (tempAbsPath "protocol-params.json") + (tempAbsPath' "byron.genesis.spec.json") + (tempAbsPath' "protocol-params.json") (rewriteParams testnetOptions) -- Generate keys @@ -142,11 +138,11 @@ testnet testnetOptions H.Conf {..} = do [ "byron" , "genesis" , "genesis" - , "--genesis-output-dir", tempAbsPath "genesis" + , "--genesis-output-dir", tempAbsPath' "genesis" , "--start-time", showUTCTimeSeconds startTime - , "--protocol-parameters-file", tempAbsPath "protocol-params.json" + , "--protocol-parameters-file", tempAbsPath' "protocol-params.json" , "--k", show @Int (securityParam testnetOptions) - , "--protocol-magic", show @Int testnetMagic + , "--protocol-magic", show @Int tNetMagic , "--n-poor-addresses", show @Int (nPoorAddresses testnetOptions) , "--n-delegate-addresses", show @Int (numBftNodes testnetOptions) , "--total-balance", show @Int (totalBalance testnetOptions) @@ -156,10 +152,10 @@ testnet testnetOptions H.Conf {..} = do , "--secret-seed", "2718281828" ] - H.writeFile (tempAbsPath "genesis/GENHASH") . S.lastLine =<< H.execCli + H.writeFile (tempAbsPath' "genesis/GENHASH") . S.lastLine =<< H.execCli [ "print-genesis-hash" , "--genesis-json" - , tempAbsPath "genesis/genesis.json" + , tempAbsPath' "genesis/genesis.json" ] let nodeIndexes = [0..numBftNodes testnetOptions - 1] @@ -168,22 +164,29 @@ testnet testnetOptions H.Conf {..} = do -- Launch cluster of three nodes in P2P Mode forM_ nodeIndexes $ \i -> do si <- H.noteShow $ show @Int i - nodeStdoutFile <- H.noteTempFile tempAbsPath $ "cardano-node-" <> si <> ".stdout.log" - nodeStderrFile <- H.noteTempFile tempAbsPath $ "cardano-node-" <> si <> ".stderr.log" - sprocket <- H.noteShow $ Sprocket tempBaseAbsPath (socketDir "node-" <> si) + nodeStdoutFile <- H.noteTempFile tempAbsPath' $ "cardano-node-" <> si <> ".stdout.log" + nodeStderrFile <- H.noteTempFile tempAbsPath' $ "cardano-node-" <> si <> ".stderr.log" + sprocket <- H.noteShow $ Sprocket tempBaseAbsPath' (sockDir "node-" <> si) portString <- H.note $ show @Int (allPorts L.!! i) - topologyFile <- H.noteShow $ tempAbsPath "topology-node-" <> si <> ".json" - configFile <- H.noteShow $ tempAbsPath "config-" <> si <> ".yaml" - signingKeyFile <- H.noteShow $ tempAbsPath "genesis/delegate-keys.00" <> si <> ".key" - delegationCertificateFile <- H.noteShow $ tempAbsPath "genesis/delegation-cert.00" <> si <> ".json" + topologyFile <- H.noteShow $ tempAbsPath' "topology-node-" <> si <> ".json" + configFile <- H.noteShow $ tempAbsPath' "config-" <> si <> ".yaml" + signingKeyFile <- H.noteShow $ tempAbsPath' "genesis/delegate-keys.00" <> si <> ".key" + delegationCertificateFile <- H.noteShow $ tempAbsPath' "genesis/delegation-cert.00" <> si <> ".json" - dbDir <- H.createDirectoryIfMissing $ tempAbsPath "db/node-" <> si + dbDir <- H.createDirectoryIfMissing $ tempAbsPath' "db/node-" <> si - H.lbsWriteFile (tempAbsPath "topology-node-" <> si <> ".json") $ + H.lbsWriteFile (tempAbsPath' "topology-node-" <> si <> ".json") $ mkTopologyConfig i (numBftNodes testnetOptions) allPorts (enableP2P testnetOptions) - H.writeFile (tempAbsPath "config-" <> si <> ".yaml") . L.unlines . fmap (rewriteConfiguration (enableP2P testnetOptions) i) . L.lines =<< - H.readFile (baseConfig "config-0.yaml") + byronGenesisHash <- getByronGenesisHash $ tempAbsPath' "genesis/genesis.json" + + let finalYamlConfig :: LBS.ByteString + finalYamlConfig = J.encode . J.Object + $ mconcat [ byronGenesisHash + , defaultYamlHardforkViaConfig $ AnyCardanoEra ByronEra + ] + + H.evalIO $ LBS.writeFile (tempAbsPath' "config-" <> si <> ".yaml") finalYamlConfig hNodeStdout <- H.openFile nodeStdoutFile IO.WriteMode hNodeStderr <- H.openFile nodeStderrFile IO.WriteMode @@ -206,7 +209,7 @@ testnet testnetOptions H.Conf {..} = do { IO.std_in = IO.CreatePipe , IO.std_out = IO.UseHandle hNodeStdout , IO.std_err = IO.UseHandle hNodeStderr - , IO.cwd = Just tempBaseAbsPath + , IO.cwd = Just tempBaseAbsPath' } ) ) @@ -219,16 +222,16 @@ testnet testnetOptions H.Conf {..} = do forM_ nodeIndexes $ \i -> do si <- H.noteShow $ show @Int i - sprocket <- H.noteShow $ Sprocket tempBaseAbsPath (socketDir "node-" <> si) + sprocket <- H.noteShow $ Sprocket tempBaseAbsPath' (sockDir "node-" <> si) _spocketSystemNameFile <- H.noteShow $ IO.sprocketSystemName sprocket -- TODO: Better error message need to indicate a sprocket was not created H.byDeadlineM 10 deadline "Failed to connect to node socket" $ H.assertM $ H.doesSprocketExist sprocket forM_ nodeIndexes $ \i -> do si <- H.noteShow $ show @Int i - nodeStdoutFile <- H.noteTempFile tempAbsPath $ "cardano-node-" <> si <> ".stdout.log" + nodeStdoutFile <- H.noteTempFile tempAbsPath' $ "cardano-node-" <> si <> ".stdout.log" H.assertByDeadlineIOCustom "stdout does not contain \"until genesis start time\"" deadline $ IO.fileContains "until genesis start time at" nodeStdoutFile - H.copyFile (tempAbsPath "config-1.yaml") (tempAbsPath "configuration.yaml") + H.copyFile (tempAbsPath' "config-1.yaml") (tempAbsPath' "configuration.yaml") return allNodes diff --git a/cardano-testnet/src/Testnet/Cardano.hs b/cardano-testnet/src/Testnet/Cardano.hs index 19192434ab6..fa8af137027 100644 --- a/cardano-testnet/src/Testnet/Cardano.hs +++ b/cardano-testnet/src/Testnet/Cardano.hs @@ -26,6 +26,7 @@ import Cardano.Api hiding (cardanoEra) import Control.Monad import qualified Data.Aeson as J +import Data.Bifunctor import qualified Data.ByteString.Lazy as LBS import qualified Data.HashMap.Lazy as HM import Data.List ((\\)) @@ -219,7 +220,7 @@ cardanoTestnet testnetOptions H.Conf {..} = do H.writeFile (tempAbsPath node "port") (show port) H.lbsWriteFile (tempAbsPath "byron.genesis.spec.json") - . J.encode $ defaultByronGenesisJsonValue + . J.encode $ defaultByronProtocolParamsJsonValue -- stuff execCli_ @@ -317,15 +318,13 @@ cardanoTestnet testnetOptions H.Conf {..} = do -- Set up our template shelleyDir <- H.createDirectoryIfMissing $ tempAbsPath "shelley" - -- TODO: This is fragile, we should be passing in all necessary - -- configuration files. - let sourceAlonzoGenesisSpecFile = base "cardano-testnet/files/data/alonzo/genesis.alonzo.spec.json" alonzoSpecFile <- H.noteTempFile tempAbsPath "shelley/genesis.alonzo.spec.json" - H.copyFile sourceAlonzoGenesisSpecFile alonzoSpecFile + gen <- H.evalEither $ first displayError defaultAlonzoGenesis + H.evalIO $ LBS.writeFile alonzoSpecFile $ J.encode gen + - let sourceConwayGenesisSpecFile = base "cardano-testnet/files/data/conway/genesis.conway.spec.json" conwaySpecFile <- H.noteTempFile tempAbsPath "shelley/genesis.conway.spec.json" - H.copyFile sourceConwayGenesisSpecFile conwaySpecFile + H.evalIO $ LBS.writeFile conwaySpecFile $ J.encode defaultConwayGenesis execCli_ [ "genesis", "create" diff --git a/cardano-testnet/src/Testnet/Commands/Genesis.hs b/cardano-testnet/src/Testnet/Commands/Genesis.hs index 01fd9f70710..5fb9915666a 100644 --- a/cardano-testnet/src/Testnet/Commands/Genesis.hs +++ b/cardano-testnet/src/Testnet/Commands/Genesis.hs @@ -5,7 +5,9 @@ module Testnet.Commands.Genesis ( createShelleyGenesisInitialTxIn , createByronGenesis - , defaultByronGenesisJsonValue + , defaultAlonzoGenesis + , defaultConwayGenesis + , defaultByronProtocolParamsJsonValue ) where import Prelude @@ -13,12 +15,27 @@ import Prelude import Control.Monad.Catch import Control.Monad.IO.Class import Data.Aeson +import Data.Bifunctor +import qualified Data.Map.Strict as Map +import Data.Ratio import Data.Time.Clock (UTCTime) +import Data.Word import GHC.Stack (HasCallStack, withFrozenCallStack) +import Cardano.Ledger.Alonzo.Core (CoinPerWord (..)) +import Cardano.Ledger.Alonzo.Genesis (AlonzoGenesis (..)) +import Cardano.Ledger.Alonzo.Scripts +import Cardano.Ledger.BaseTypes +import Cardano.Ledger.Coin +import Cardano.Ledger.Conway.Genesis +import Cardano.Ledger.Keys + +import qualified Cardano.Api.Shelley as Api + import Hedgehog.Extras.Stock.Time (showUTCTimeSeconds) import Hedgehog.Internal.Property +import Cardano.Ledger.Crypto (StandardCrypto) import Testnet.Options import Testnet.Util.Process @@ -65,8 +82,8 @@ createShelleyGenesisInitialTxIn testnetMagic vKeyFp = -- | We need a Byron genesis in order to be able to hardfork to the later Shelley based eras. -- The values here don't matter as the testnet conditions are ultimately determined -- by the Shelley genesis. -defaultByronGenesisJsonValue :: Value -defaultByronGenesisJsonValue = +defaultByronProtocolParamsJsonValue :: Value +defaultByronProtocolParamsJsonValue = object [ "heavyDelThd" .= toJSON @String "300000000000" , "maxBlockSize" .= toJSON @String "2000000" @@ -91,3 +108,89 @@ defaultByronGenesisJsonValue = , "updateVoteThd" .= toJSON @String "1000000000000" ] + +instance Api.Error AlonzoGenesisError where + displayError (AlonzoGenErrCostModels e) = + "Error in Alonzo genesis cost models: " <> show e + displayError (AlonzoGenErrTooMuchPrecision r) = + "Too much precision for bounded rational in Alonzo genesis: " ++ show r + +data AlonzoGenesisError + = AlonzoGenErrTooMuchPrecision Rational + | AlonzoGenErrCostModels Api.ProtocolParametersConversionError + deriving Show + +defaultAlonzoGenesis :: Either AlonzoGenesisError AlonzoGenesis +defaultAlonzoGenesis = do + es <- checkBoundedRational priceExecStepsRat + ms <- checkBoundedRational priceMemStepsRat + let execPrices = Prices es ms + costModels <- first AlonzoGenErrCostModels + $ Api.toAlonzoCostModels apiCostModels + return $ AlonzoGenesis + { agCoinsPerUTxOWord = CoinPerWord $ Coin 34482 + , agCostModels = costModels + , agPrices = execPrices + , agMaxTxExUnits = maxTxExUnits + , agMaxBlockExUnits = maxBlockExUnits + , agMaxValSize = 5000 + , agCollateralPercentage = 150 + , agMaxCollateralInputs = 3 + } + where + + priceExecStepsRat = promoteRatio $ 721 % (10000000 :: Word64) + priceMemStepsRat = promoteRatio $ 577 % (10000 :: Word64) + + checkBoundedRational r = + case boundRational r of + Nothing -> Left $ AlonzoGenErrTooMuchPrecision r + Just s -> return s + + maxTxExUnits = Api.toAlonzoExUnits + $ Api.ExecutionUnits + { Api.executionSteps = 16000000 + , Api.executionMemory = 10000000000 + } + maxBlockExUnits = Api.toAlonzoExUnits + $ Api.ExecutionUnits + { Api.executionSteps = 40000000000 + , Api.executionMemory = 80000000 + } + apiCostModels = + let pv1 = Api.AnyPlutusScriptVersion Api.PlutusScriptV1 + pv2 = Api.AnyPlutusScriptVersion Api.PlutusScriptV2 + in mconcat [ Map.singleton pv1 defaultV1CostModel + , Map.singleton pv2 defaultV2CostModel + ] + defaultV1CostModel = Api.CostModel + [ 4, 1000, 100, 103599, 1, 621, 29175, 150000, 1000, 150000, 61516, 100, 150000, 150000 + , 150000, 32, 150000, 29773, 150000, 0, 150000, 0, 1, 118, 150000, 150000, 32, 136542 + , 82363, 5000, 150000, 179690, 150000, 0, 118, 1, 150000, 145276, 1, 32, 32, 150000, 1 + , 1, 0, 4, 32, 32, 150000, 32, 1, 32, 248, 0, 100, 0, 32, 118, 29773, 1, 29773, 29175 + , 1, 1, 1, 150000, 150000, 29773, 150000, 1, 1000, 1, 1366, 32, 0, 150000, 1, 32, 32 + , 197209, 8, 150000, 150000, 150000, 148000, 1, 100, 150000, 150000, 1326, 100, 197209 + , 425507, 0, 100, 2477736, 148000, 150000, 150000, 1000, 1, 11218, 396231, 248, 1, 0 + , 10000, 0, 150000, 150000, 1, 29773, 1, 3345831, 32, 32, 1, 4, 1, 32, 247, 150000, 118 + , 100, 1, 1, 100, 0, 2477736, 425507, 1, 32, 150000, 150000, 32, 4, 32, 32, 29773, 1 + , 103599, 1000, 1, 32, 148000, 29773, 8, 425507, 32, 1000, 148000, 1, 32, 0, 150000, 0 + , 32, 112536, 1, 497, 425507, 1, 0, 1, 100, 150000 + ] + defaultV2CostModel = Api.CostModel + [ 205665, 812, 1, 1, 1000, 571, 0, 1, 1000, 24177, 4, 1, 1000, 32, 117366, 10475, 4 + , 23000, 100, 23000, 100, 23000, 100, 23000, 100, 23000, 100, 23000, 100, 100, 100 + , 23000, 100, 19537, 32, 175354, 32, 46417, 4, 221973, 511, 0, 1, 89141, 32, 497525 + , 14068, 4, 2, 196500, 453240, 220, 0, 1, 1, 1000, 28662, 4, 2, 245000, 216773, 62 + , 1, 1060367, 12586, 1, 208512, 421, 1, 187000, 1000, 52998, 1, 80436, 32, 43249, 32 + , 1000, 32, 80556, 1, 57667, 4, 1000, 10, 197145, 156, 1, 197145, 156, 1, 204924, 473 + , 1, 208896, 511, 1, 52467, 32, 64832, 32, 65493, 32, 22558, 32, 16563, 32, 76511, 32 + , 196500, 453240, 220, 0, 1, 1, 69522, 11687, 0, 1, 60091, 32, 196500, 453240, 220, 0 + , 1, 1, 196500, 453240, 220, 0, 1, 1, 1159724, 392670, 0, 2, 806990, 30482, 4, 1927926 + , 82523, 4, 265318, 0, 4, 0, 85931, 32, 205665, 812, 1, 1, 41182, 32, 212342, 32, 31220 + , 32, 32696, 32, 43357, 32, 32247, 32, 38314, 32, 35892428, 10, 9462713, 1021, 10, 38887044 + , 32947, 10 + ] + + +defaultConwayGenesis :: ConwayGenesis StandardCrypto +defaultConwayGenesis = ConwayGenesis { cgGenDelegs = GenDelegs mempty} diff --git a/cardano-testnet/src/Testnet/Conf.hs b/cardano-testnet/src/Testnet/Conf.hs index 0bd0aec7f6b..9ff218f5e9b 100644 --- a/cardano-testnet/src/Testnet/Conf.hs +++ b/cardano-testnet/src/Testnet/Conf.hs @@ -27,14 +27,13 @@ data Conf = Conf , tempRelPath :: FilePath , tempBaseAbsPath :: FilePath , logDir :: FilePath - , base :: FilePath , socketDir :: FilePath , configurationTemplate :: Maybe FilePath , testnetMagic :: Int } deriving (Eq, Show) -mkConf :: ProjectBase -> Maybe YamlFilePath -> FilePath -> Maybe Int -> H.Integration Conf -mkConf (ProjectBase base') mConfigTemplate tempAbsPath' maybeMagic = do +mkConf :: Maybe YamlFilePath -> FilePath -> Maybe Int -> H.Integration Conf +mkConf mConfigTemplate tempAbsPath' maybeMagic = do testnetMagic' <- H.noteShowIO $ maybe (IO.randomRIO (1000, 2000)) return maybeMagic tempBaseAbsPath' <- H.noteShow $ FP.takeDirectory tempAbsPath' tempRelPath' <- H.noteShow $ FP.makeRelative tempBaseAbsPath' tempAbsPath' @@ -47,7 +46,6 @@ mkConf (ProjectBase base') mConfigTemplate tempAbsPath' maybeMagic = do , tempRelPath = tempRelPath' , tempBaseAbsPath = tempBaseAbsPath' , logDir = logDir' - , base = base' , socketDir = socketDir' , configurationTemplate = configTemplate , testnetMagic = testnetMagic' diff --git a/cardano-testnet/src/Testnet/Options.hs b/cardano-testnet/src/Testnet/Options.hs index 8baf6c54d31..acdb77f82f1 100644 --- a/cardano-testnet/src/Testnet/Options.hs +++ b/cardano-testnet/src/Testnet/Options.hs @@ -7,6 +7,7 @@ module Testnet.Options ( BabbageTestnetOptions(..) + , defaultShelleyOnlyYamlConfig , defaultTestnetOptions , defaultYamlHardforkViaConfig ) where @@ -44,11 +45,10 @@ defaultTestnetOptions = BabbageTestnetOptions , babbageNodeLoggingFormat = NodeLoggingFormatAsJson } --- | Configuration value that allows you to hardfork to any Cardano era --- at epoch 0. -defaultYamlHardforkViaConfig :: AnyCardanoEra -> KeyMapAeson.KeyMap Aeson.Value -defaultYamlHardforkViaConfig era = - mconcat $ map (uncurry KeyMapAeson.singleton) + +defaultYamlConfig :: [KeyMapAeson.KeyMap Aeson.Value] +defaultYamlConfig = + map (uncurry KeyMapAeson.singleton) [ -- The consensus protocol to use ("Protocol", "Cardano") @@ -91,7 +91,29 @@ defaultYamlHardforkViaConfig era = , ("setupBackends", Aeson.Array $ Vector.fromList ["KatipBK"]) , ("defaultBackends", Aeson.Array $ Vector.fromList ["KatipBK"]) , ("options", Aeson.object mempty) - ] ++ tracers ++ protocolVersions era ++ hardforkViaConfig era + ] + + +defaultShelleyOnlyYamlConfig :: KeyMapAeson.KeyMap Aeson.Value +defaultShelleyOnlyYamlConfig = + let shelleyOnly = mconcat $ map (uncurry KeyMapAeson.singleton) + [ ("LastKnownBlockVersion-Major", Aeson.Number 2) + , ("LastKnownBlockVersion-Minor", Aeson.Number 0) + , ("LastKnownBlockVersion-Alt", Aeson.Number 0) + , ("Protocol", "TPraos") + ] + in shelleyOnly <> mconcat defaultYamlConfig + +-- | Configuration value that allows you to hardfork to any Cardano era +-- at epoch 0. +defaultYamlHardforkViaConfig :: AnyCardanoEra -> KeyMapAeson.KeyMap Aeson.Value +defaultYamlHardforkViaConfig era = + mconcat $ concat + [ defaultYamlConfig + , tracers + , protocolVersions era + , hardforkViaConfig era + ] where -- The protocol version number gets used by block producing nodes as part @@ -240,33 +262,34 @@ defaultYamlHardforkViaConfig era = , (proxyName (Proxy @TraceTxSubmissionProtocol), Aeson.Bool False) ] - defaultScribes :: Aeson.Value - defaultScribes = - Aeson.Array $ Vector.fromList - [ Aeson.Array $ Vector.fromList ["FileSK","logs/mainnet.log"] - , Aeson.Array $ Vector.fromList ["StdoutSK","stdout"] - ] +defaultScribes :: Aeson.Value +defaultScribes = + Aeson.Array $ Vector.fromList + [ Aeson.Array $ Vector.fromList ["FileSK","logs/mainnet.log"] + , Aeson.Array $ Vector.fromList ["StdoutSK","stdout"] + ] - rotationObject :: Aeson.Value - rotationObject = - Aeson.Object $ - mconcat $ map (uncurry KeyMapAeson.singleton) - [ ("rpLogLimitBytes", Aeson.Number 5000000) - , ("rpKeepFilesNum", Aeson.Number 3) - , ("rpMaxAgeHours", Aeson.Number 24) - ] - setupScribes :: Aeson.Value - setupScribes = - Aeson.Array $ Vector.fromList - [ Aeson.Object $ mconcat $ map (uncurry KeyMapAeson.singleton) - [ ("scKind", "FileSK") - , ("scName", "logs/node.log") - , ("scFormat", "ScJson") - ] - , Aeson.Object $ mconcat $ map (uncurry KeyMapAeson.singleton) - [ ("scKind", "StdoutSK") - , ("scName", "stdout") - , ("scFormat", "ScJson") - ] +rotationObject :: Aeson.Value +rotationObject = + Aeson.Object $ + mconcat $ map (uncurry KeyMapAeson.singleton) + [ ("rpLogLimitBytes", Aeson.Number 5000000) + , ("rpKeepFilesNum", Aeson.Number 3) + , ("rpMaxAgeHours", Aeson.Number 24) ] + +setupScribes :: Aeson.Value +setupScribes = + Aeson.Array $ Vector.fromList + [ Aeson.Object $ mconcat $ map (uncurry KeyMapAeson.singleton) + [ ("scKind", "FileSK") + , ("scName", "logs/node.log") + , ("scFormat", "ScJson") + ] + , Aeson.Object $ mconcat $ map (uncurry KeyMapAeson.singleton) + [ ("scKind", "StdoutSK") + , ("scName", "stdout") + , ("scFormat", "ScJson") + ] + ] diff --git a/cardano-testnet/src/Testnet/Run.hs b/cardano-testnet/src/Testnet/Run.hs index a9e4345adde..1809b271f0d 100644 --- a/cardano-testnet/src/Testnet/Run.hs +++ b/cardano-testnet/src/Testnet/Run.hs @@ -11,18 +11,15 @@ import qualified Control.Concurrent as IO import qualified Control.Concurrent.STM as STM import qualified Hedgehog as H import qualified Hedgehog.Extras.Test.Base as H -import qualified Hedgehog.Extras.Test.Process as H import qualified System.Console.ANSI as ANSI -import qualified System.Directory as IO import qualified System.Exit as IO import qualified System.IO as IO import qualified Testnet.Conf as H import qualified Testnet.Util.Base as H testnetProperty :: Maybe Int -> (H.Conf -> H.Integration ()) -> H.Property -testnetProperty maybeTestnetMagic tn = H.integrationRetryWorkspace 2 "testnet" $ \tempAbsPath' -> do - base <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase - conf <- H.mkConf (H.ProjectBase base) Nothing tempAbsPath' maybeTestnetMagic +testnetProperty maybeTestnetMagic tn = H.integrationRetryWorkspace 2 "testnet" $ \workspaceDir -> do + conf <- H.mkConf Nothing workspaceDir maybeTestnetMagic -- Fork a thread to keep alive indefinitely any resources allocated by testnet. void . H.evalM . liftResourceT . resourceForkIO . forever . liftIO $ IO.threadDelay 10000000 diff --git a/cardano-testnet/src/Testnet/Shelley.hs b/cardano-testnet/src/Testnet/Shelley.hs index 0a9f4ca8b27..d00d994ee19 100644 --- a/cardano-testnet/src/Testnet/Shelley.hs +++ b/cardano-testnet/src/Testnet/Shelley.hs @@ -19,8 +19,9 @@ import Control.Monad import Control.Monad.IO.Class (MonadIO (liftIO)) import Control.Monad.Trans.Resource (MonadResource (liftResourceT), resourceForkIO) import Data.Aeson (ToJSON (toJSON), Value) +import Data.Bifunctor import Data.ByteString.Lazy (ByteString) -import Data.Functor +import qualified Data.ByteString.Lazy as LBS import Data.List ((\\)) import Data.Maybe import Data.String @@ -32,6 +33,7 @@ import Ouroboros.Network.PeerSelection.LedgerPeers (UseLedgerAfter (.. import Ouroboros.Network.PeerSelection.RelayAccessPoint (RelayAccessPoint (..)) import System.FilePath.Posix (()) +import Cardano.Api hiding (Value) import qualified Cardano.Node.Configuration.Topology as NonP2P import qualified Cardano.Node.Configuration.TopologyP2P as P2P import qualified Control.Concurrent as IO @@ -50,9 +52,9 @@ import qualified Hedgehog.Extras.Stock.Time as DTC import qualified Hedgehog.Extras.Test.Base as H import qualified Hedgehog.Extras.Test.File as H import qualified Hedgehog.Extras.Test.Network as H -import qualified Hedgehog.Extras.Test.Process as H import qualified System.Directory as IO import qualified System.Info as OS +import Testnet.Options (defaultShelleyOnlyYamlConfig) import Testnet.Commands.Genesis import qualified Testnet.Conf as H @@ -89,14 +91,6 @@ defaultTestnetOptions = ShelleyTestnetOptions , shelleyEnableP2P = False } --- TODO: We need to refactor this to directly check the parsed configuration --- and fail with a suitable error message. --- | Rewrite a line in the configuration file -rewriteConfiguration :: Bool -> String -> String -rewriteConfiguration True "EnableP2P: False" = "EnableP2P: True" -rewriteConfiguration False "EnableP2P: True" = "EnableP2P: False" -rewriteConfiguration _ s = s - ifaceAddress :: String ifaceAddress = "127.0.0.1" @@ -178,15 +172,13 @@ shelleyTestnet testnetOptions H.Conf {..} = do let poolAddrs = ("pool-owner" <>) <$> poolNodesN let addrs = userAddrs <> poolAddrs - -- TODO: This is fragile, we should be passing in all necessary - -- configuration files. - let sourceAlonzoGenesisSpecFile = base "cardano-testnet/files/data/alonzo/genesis.alonzo.spec.json" alonzoSpecFile <- H.noteTempFile tempAbsPath "genesis.alonzo.spec.json" - H.copyFile sourceAlonzoGenesisSpecFile alonzoSpecFile + gen <- H.evalEither $ first displayError defaultAlonzoGenesis + H.evalIO $ LBS.writeFile alonzoSpecFile $ J.encode gen + - let sourceConwayGenesisSpecFile = base "cardano-testnet/files/data/conway/genesis.conway.spec.json" conwaySpecFile <- H.noteTempFile tempAbsPath "genesis.conway.spec.json" - H.copyFile sourceConwayGenesisSpecFile conwaySpecFile + H.evalIO $ LBS.writeFile conwaySpecFile $ J.encode defaultConwayGenesis -- Set up our template execCli_ @@ -387,10 +379,8 @@ shelleyTestnet testnetOptions H.Conf {..} = do -------------------------------- -- Launch cluster of three nodes + H.evalIO $ LBS.writeFile (tempAbsPath "configuration.yaml") $ J.encode defaultShelleyOnlyYamlConfig - H.readFile (base "configuration/chairman/shelley-only/configuration.yaml") - <&> L.unlines . fmap (rewriteConfiguration (shelleyEnableP2P testnetOptions)) . L.lines - >>= H.writeFile (tempAbsPath "configuration.yaml") allNodeRuntimes <- forM allNodes $ \node -> startNode tempBaseAbsPath tempAbsPath logDir socketDir node @@ -431,8 +421,7 @@ shelleyTestnet testnetOptions H.Conf {..} = do hprop_testnet :: H.Property hprop_testnet = H.integrationRetryWorkspace 2 "shelley-testnet" $ \tempAbsPath' -> do - base <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase - conf <- H.mkConf (H.ProjectBase base) Nothing tempAbsPath' Nothing + conf <- H.mkConf Nothing tempAbsPath' Nothing void . H.evalM . liftResourceT . resourceForkIO . forever . liftIO $ IO.threadDelay 10000000 diff --git a/cardano-testnet/src/Testnet/Topology.hs b/cardano-testnet/src/Testnet/Topology.hs new file mode 100644 index 00000000000..b72d9e7eb64 --- /dev/null +++ b/cardano-testnet/src/Testnet/Topology.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE OverloadedStrings #-} + +module Testnet.Topology + ( defaultMainnetTopology + ) where + +import Cardano.Node.Configuration.Topology + + +defaultMainnetTopology :: NetworkTopology +defaultMainnetTopology = + let single = RemoteAddress + { raAddress = "relays-new.cardano-mainnet.iohk.io" + , raPort = 3001 + , raValency= 2 + } + in RealNodeTopology [single] diff --git a/cardano-testnet/src/Testnet/Util/Base.hs b/cardano-testnet/src/Testnet/Util/Base.hs index 84dfb9aba45..73093fa44a6 100644 --- a/cardano-testnet/src/Testnet/Util/Base.hs +++ b/cardano-testnet/src/Testnet/Util/Base.hs @@ -15,6 +15,8 @@ import qualified Hedgehog.Extras.Test.Base as H integration :: HasCallStack => H.Integration () -> H.Property integration f = GHC.withFrozenCallStack $ H.withTests 1 $ H.propertyOnce f +-- | The 'FilePath' in '(FilePath -> H.Integration ())' is the work space directory. +-- This is created (and returned) via 'H.workspace'. integrationRetryWorkspace :: HasCallStack => Int -> FilePath -> (FilePath -> H.Integration ()) -> H.Property integrationRetryWorkspace n workspaceName f = GHC.withFrozenCallStack $ integration $ H.retry n $ \i -> diff --git a/cardano-testnet/test/cardano-testnet-test/Test/Cli/Alonzo/LeadershipSchedule.hs b/cardano-testnet/test/cardano-testnet-test/Test/Cli/Alonzo/LeadershipSchedule.hs index 575a3a9b85b..5361fede5be 100644 --- a/cardano-testnet/test/cardano-testnet-test/Test/Cli/Alonzo/LeadershipSchedule.hs +++ b/cardano-testnet/test/cardano-testnet-test/Test/Cli/Alonzo/LeadershipSchedule.hs @@ -31,9 +31,7 @@ import qualified Hedgehog as H import qualified Hedgehog.Extras.Test.Base as H import qualified Hedgehog.Extras.Test.Concurrent as H import qualified Hedgehog.Extras.Test.File as H -import qualified Hedgehog.Extras.Test.Process as H import Prelude -import qualified System.Directory as IO import System.FilePath (()) import qualified System.Info as SYS import qualified Testnet.Util.Process as H @@ -53,9 +51,8 @@ import Testnet.Util.Runtime hprop_leadershipSchedule :: Property hprop_leadershipSchedule = integrationRetryWorkspace 2 "alonzo-leadership-schedule" $ \tempAbsBasePath' -> do H.note_ SYS.os - base <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase conf@Conf { tempBaseAbsPath, tempAbsPath } <- H.noteShowM $ - mkConf (ProjectBase base) Nothing tempAbsBasePath' Nothing + mkConf Nothing tempAbsBasePath' Nothing let fastTestnetOptions = CardanoOnlyTestnetOptions cardanoDefaultTestnetOptions { cardanoEpochLength = 500 @@ -73,7 +70,6 @@ hprop_leadershipSchedule = integrationRetryWorkspace 2 "alonzo-leadership-schedu execConfig <- H.headM (bftSprockets tr) >>= H.mkExecConfig tempBaseAbsPath -- First we note all the relevant files - H.note_ base work <- H.note tempAbsPath -- We get our UTxOs from here diff --git a/cardano-testnet/test/cardano-testnet-test/Test/Cli/Babbage/LeadershipSchedule.hs b/cardano-testnet/test/cardano-testnet-test/Test/Cli/Babbage/LeadershipSchedule.hs index a2c35aab2de..cfa69542d8e 100644 --- a/cardano-testnet/test/cardano-testnet-test/Test/Cli/Babbage/LeadershipSchedule.hs +++ b/cardano-testnet/test/cardano-testnet-test/Test/Cli/Babbage/LeadershipSchedule.hs @@ -32,8 +32,6 @@ import qualified Data.Time.Clock as DTC import qualified Hedgehog as H import qualified Hedgehog.Extras.Test.Base as H import qualified Hedgehog.Extras.Test.File as H -import qualified Hedgehog.Extras.Test.Process as H -import qualified System.Directory as IO import qualified System.Info as SYS import qualified Testnet.Util.Base as H @@ -46,9 +44,8 @@ import Testnet.Util.Runtime hprop_leadershipSchedule :: Property hprop_leadershipSchedule = H.integrationRetryWorkspace 2 "babbage-leadership-schedule" $ \tempAbsBasePath' -> do H.note_ SYS.os - base <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase conf@Conf { tempBaseAbsPath, tempAbsPath } <- H.noteShowM $ - mkConf (ProjectBase base) Nothing tempAbsBasePath' Nothing + mkConf Nothing tempAbsBasePath' Nothing work <- H.createDirectoryIfMissing $ tempAbsPath "work" diff --git a/cardano-testnet/test/cardano-testnet-test/Test/Cli/Babbage/StakeSnapshot.hs b/cardano-testnet/test/cardano-testnet-test/Test/Cli/Babbage/StakeSnapshot.hs index f95be121add..54f0c58f5aa 100644 --- a/cardano-testnet/test/cardano-testnet-test/Test/Cli/Babbage/StakeSnapshot.hs +++ b/cardano-testnet/test/cardano-testnet-test/Test/Cli/Babbage/StakeSnapshot.hs @@ -25,7 +25,6 @@ import qualified Data.Text as Text import qualified Data.Text.Encoding as Text import qualified Data.Time.Clock as DTC import GHC.Stack (callStack) -import qualified System.Directory as IO import System.FilePath (()) import qualified System.Info as SYS @@ -36,7 +35,6 @@ import Hedgehog (Property, (===)) import qualified Hedgehog as H import qualified Hedgehog.Extras.Test.Base as H import qualified Hedgehog.Extras.Test.File as H -import qualified Hedgehog.Extras.Test.Process as H import qualified Testnet.Util.Base as H import qualified Testnet.Util.Process as H import Testnet.Util.Process @@ -45,9 +43,8 @@ import Testnet.Util.Runtime hprop_stakeSnapshot :: Property hprop_stakeSnapshot = H.integrationRetryWorkspace 2 "babbage-stake-snapshot" $ \tempAbsBasePath' -> do H.note_ SYS.os - base <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase conf@Conf { tempBaseAbsPath, tempAbsPath } <- H.noteShowM $ - mkConf (ProjectBase base) Nothing tempAbsBasePath' Nothing + mkConf Nothing tempAbsBasePath' Nothing work <- H.createDirectoryIfMissing $ tempAbsPath "work" diff --git a/cardano-testnet/test/cardano-testnet-test/Test/Cli/KesPeriodInfo.hs b/cardano-testnet/test/cardano-testnet-test/Test/Cli/KesPeriodInfo.hs index bbb0777a5c9..3ea4aa8c676 100644 --- a/cardano-testnet/test/cardano-testnet-test/Test/Cli/KesPeriodInfo.hs +++ b/cardano-testnet/test/cardano-testnet-test/Test/Cli/KesPeriodInfo.hs @@ -27,8 +27,6 @@ import qualified Data.Text as T import qualified Hedgehog as H import qualified Hedgehog.Extras.Test.Base as H import qualified Hedgehog.Extras.Test.File as H -import qualified Hedgehog.Extras.Test.Process as H -import qualified System.Directory as IO import qualified System.Info as SYS import qualified Testnet.Util.Base as H import qualified Testnet.Util.Process as H @@ -41,11 +39,9 @@ import Testnet.Util.Runtime hprop_kes_period_info :: Property hprop_kes_period_info = H.integrationRetryWorkspace 2 "kes-period-info" $ \tempAbsBasePath' -> do H.note_ SYS.os - base <- H.note =<< H.evalIO . IO.canonicalizePath =<< H.getProjectBase conf@Conf { tempBaseAbsPath, tempAbsPath } -- TODO: Move yaml filepath specification into individual node options - <- H.noteShowM $ mkConf (ProjectBase base) Nothing - tempAbsBasePath' Nothing + <- H.noteShowM $ mkConf Nothing tempAbsBasePath' Nothing let fastTestnetOptions = CardanoOnlyTestnetOptions $ cardanoDefaultTestnetOptions { cardanoNodes = cardanoDefaultTestnetNodeOptions diff --git a/cardano-testnet/test/cardano-testnet-test/Test/Cli/QuerySlotNumber.hs b/cardano-testnet/test/cardano-testnet-test/Test/Cli/QuerySlotNumber.hs index aa7d1a5345e..0cda27953c6 100644 --- a/cardano-testnet/test/cardano-testnet-test/Test/Cli/QuerySlotNumber.hs +++ b/cardano-testnet/test/cardano-testnet-test/Test/Cli/QuerySlotNumber.hs @@ -42,7 +42,7 @@ hprop_querySlotNumber = H.integrationRetryWorkspace 2 "query-slot-number" $ \tem base <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase configurationTemplate <- H.noteShow $ base "configuration/defaults/byron-mainnet/configuration.yaml" conf@Conf { tempBaseAbsPath } <- H.noteShowM $ - mkConf (ProjectBase base) (Just $ YamlFilePath configurationTemplate) tempAbsBasePath' Nothing + mkConf (Just $ YamlFilePath configurationTemplate) tempAbsBasePath' Nothing let testnetOptions = BabbageOnlyTestnetOptions $ babbageDefaultTestnetOptions diff --git a/cardano-testnet/test/cardano-testnet-test/Test/FoldBlocks.hs b/cardano-testnet/test/cardano-testnet-test/Test/FoldBlocks.hs index f2cabba99d8..f3311cd663d 100644 --- a/cardano-testnet/test/cardano-testnet-test/Test/FoldBlocks.hs +++ b/cardano-testnet/test/cardano-testnet-test/Test/FoldBlocks.hs @@ -37,11 +37,7 @@ prop_foldBlocks :: H.Property prop_foldBlocks = H.integrationRetryWorkspace 2 "foldblocks" $ \tempAbsBasePath' -> do -- Start testnet - base <- HE.noteM $ H.evalIO . IO.canonicalizePath =<< HE.getProjectBase - conf <- HE.noteShowM $ - TN.mkConf (TN.ProjectBase base) Nothing - (tempAbsBasePath' <> "/") - Nothing + conf <- HE.noteShowM $ TN.mkConf Nothing (tempAbsBasePath' <> "/") Nothing let options = CardanoOnlyTestnetOptions $ cardanoDefaultTestnetOptions -- NB! The `activeSlotsCoeff` value is very important for diff --git a/cardano-testnet/test/cardano-testnet-test/Test/Node/Shutdown.hs b/cardano-testnet/test/cardano-testnet-test/Test/Node/Shutdown.hs index 858ecc63204..fdc60c6244b 100644 --- a/cardano-testnet/test/cardano-testnet-test/Test/Node/Shutdown.hs +++ b/cardano-testnet/test/cardano-testnet-test/Test/Node/Shutdown.hs @@ -1,5 +1,4 @@ {-# LANGUAGE DisambiguateRecordFields #-} -{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} @@ -8,10 +7,15 @@ module Test.Node.Shutdown ( hprop_shutdown ) where +import Cardano.Api import Control.Monad +import Data.Aeson +import Data.Bifunctor +import qualified Data.ByteString.Lazy as LBS import Data.Functor ((<&>)) import qualified Data.List as L import Data.Maybe +import qualified Data.Time.Clock as DTC import Hedgehog (Property, (===)) import Prelude import System.FilePath (()) @@ -19,46 +23,106 @@ import System.FilePath (()) import qualified Hedgehog as H import qualified Hedgehog.Extras.Stock.IO.Network.Socket as IO import qualified Hedgehog.Extras.Stock.IO.Network.Sprocket as IO +import Hedgehog.Extras.Stock.Time (formatIso8601) import qualified Hedgehog.Extras.Test.Base as H import qualified Hedgehog.Extras.Test.Concurrent as H import qualified Hedgehog.Extras.Test.File as H import qualified Hedgehog.Extras.Test.Process as H -import qualified System.Directory as IO import qualified System.Exit as IO import qualified System.IO as IO import qualified System.Process as IO import qualified Testnet.Util.Base as H import Cardano.Testnet -import Testnet.Util.Process (procNode) +import Testnet.Commands.Genesis +import Testnet.Options +import Testnet.Topology +import Testnet.Util.Process (execCli_, procNode) +import Testnet.Utils {- HLINT ignore "Redundant <&>" -} hprop_shutdown :: Property hprop_shutdown = H.integrationRetryWorkspace 2 "shutdown" $ \tempAbsBasePath' -> do - base <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase - Conf { tempBaseAbsPath, tempAbsPath, logDir, socketDir } <- H.noteShowM $ - mkConf (ProjectBase base) Nothing tempAbsBasePath' Nothing - + conf <- H.noteShowM $ + mkConf Nothing tempAbsBasePath' Nothing + let tempBaseAbsPath' = tempBaseAbsPath conf + tempAbsPath' = tempAbsPath conf + logDir' = logDir conf + socketDir' = socketDir conf + testnetMagic' = testnetMagic conf [port] <- H.noteShowIO $ IO.allocateRandomPorts 1 - sprocket <- H.noteShow $ IO.Sprocket tempBaseAbsPath (socketDir "node") + sprocket <- H.noteShow $ IO.Sprocket tempBaseAbsPath' (socketDir' "node") H.diff (L.length (IO.sprocketArgumentName sprocket)) (<=) IO.maxSprocketArgumentNameLength - nodeStdoutFile <- H.noteTempFile logDir "node.stdout.log" - nodeStderrFile <- H.noteTempFile logDir "node.stderr.log" + nodeStdoutFile <- H.noteTempFile logDir' "node.stdout.log" + nodeStderrFile <- H.noteTempFile logDir' "node.stderr.log" hNodeStdout <- H.openFile nodeStdoutFile IO.WriteMode hNodeStderr <- H.openFile nodeStderrFile IO.WriteMode + -- We need to create the relevant genesis files to start the node + -- 1. Create Byron genesis + + H.lbsWriteFile (tempAbsPath' "byron.genesis.spec.json") + . encode $ defaultByronProtocolParamsJsonValue + + startTime <- H.noteShowIO DTC.getCurrentTime + createByronGenesis + testnetMagic' + startTime + babbageDefaultTestnetOptions + (tempAbsPath' "byron.genesis.spec.json") + (tempAbsPath' "byron") + + shelleyDir <- H.createDirectoryIfMissing $ tempAbsPath' "shelley" + + -- 2. Create Alonzo genesis + alonzoBabbageTestGenesisJsonTargetFile <- H.noteShow $ tempAbsPath' shelleyDir "genesis.alonzo.spec.json" + gen <- H.evalEither $ first displayError defaultAlonzoGenesis + H.evalIO $ LBS.writeFile alonzoBabbageTestGenesisJsonTargetFile $ encode gen + + -- 2. Create Conway genesis + conwayBabbageTestGenesisJsonTargetFile <- H.noteShow $ tempAbsPath' shelleyDir "genesis.conway.spec.json" + H.evalIO $ LBS.writeFile conwayBabbageTestGenesisJsonTargetFile $ encode defaultConwayGenesis + + -- 4. Create Shelley genesis + execCli_ + [ "genesis", "create" + , "--testnet-magic", show @Int testnetMagic' + , "--genesis-dir", shelleyDir + , "--start-time", formatIso8601 startTime + ] + + + + + byronGenesisHash <- getByronGenesisHash $ tempAbsPath' "byron/genesis.json" + shelleyGenesisHash <- getShelleyGenesisHash (tempAbsPath' "shelley/genesis.json") "ShelleyGenesisHash" + alonzoGenesisHash <- getShelleyGenesisHash (tempAbsPath' "shelley/genesis.alonzo.json") "AlonzoGenesisHash" + + let finalYamlConfig :: LBS.ByteString + finalYamlConfig = encode . Object + $ mconcat [ byronGenesisHash + , shelleyGenesisHash + , alonzoGenesisHash + , defaultYamlHardforkViaConfig (AnyCardanoEra BabbageEra)] + + H.evalIO $ LBS.writeFile (tempAbsPath' "configuration.yaml") finalYamlConfig + + H.evalIO $ LBS.writeFile (tempAbsPath' "mainnet-topology.json") + $ encode defaultMainnetTopology + + -- TODO: Stopped here -- Run cardano-node with pipe as stdin. Use 0 file descriptor as shutdown-ipc (mStdin, _mStdout, _mStderr, pHandle, _releaseKey) <- H.createProcess =<< ( procNode [ "run" - , "--config", base "configuration/cardano/mainnet-config.json" - , "--topology", base "configuration/cardano/mainnet-topology.json" - , "--database-path", tempAbsPath "db" + , "--config", tempAbsPath' "configuration.yaml" + , "--topology", tempAbsPath' "mainnet-topology.json" + , "--database-path", tempAbsPath' "db" , "--socket-path", IO.sprocketArgumentName sprocket , "--host-addr", "127.0.0.1" , "--port", show @Int port @@ -68,7 +132,7 @@ hprop_shutdown = H.integrationRetryWorkspace 2 "shutdown" $ \tempAbsBasePath' -> { IO.std_in = IO.CreatePipe , IO.std_out = IO.UseHandle hNodeStdout , IO.std_err = IO.UseHandle hNodeStderr - , IO.cwd = Just tempBaseAbsPath + , IO.cwd = Just tempBaseAbsPath' } ) ) diff --git a/cardano-testnet/test/cardano-testnet-test/Test/ShutdownOnSlotSynced.hs b/cardano-testnet/test/cardano-testnet-test/Test/ShutdownOnSlotSynced.hs index d3771f6ee3c..cbff3a98d13 100644 --- a/cardano-testnet/test/cardano-testnet-test/Test/ShutdownOnSlotSynced.hs +++ b/cardano-testnet/test/cardano-testnet-test/Test/ShutdownOnSlotSynced.hs @@ -17,7 +17,6 @@ import Data.Either (isRight) import Data.Maybe import GHC.IO.Exception (ExitCode (ExitSuccess)) import GHC.Stack (callStack) -import qualified System.Directory as IO import Hedgehog (Property, (===)) import qualified Hedgehog as H @@ -31,10 +30,9 @@ import Testnet.Util.Runtime (TestnetRuntime (..)) hprop_shutdownOnSlotSynced :: Property hprop_shutdownOnSlotSynced = H.integrationRetryWorkspace 2 "shutdown-on-slot-synced" $ \tempAbsBasePath' -> do -- Start a local test net - baseDir <- H.note =<< H.noteIO . IO.canonicalizePath =<< H.getProjectBase - conf <- H.noteShowM $ - -- TODO: Move yaml filepath specification into individual node options - mkConf (ProjectBase baseDir) Nothing tempAbsBasePath' Nothing + -- TODO: Move yaml filepath specification into individual node options + conf <- H.noteShowM $ mkConf Nothing tempAbsBasePath' Nothing + let maxSlot = 1500 slotLen = 0.01 let fastTestnetOptions = CardanoOnlyTestnetOptions $ cardanoDefaultTestnetOptions