Skip to content

Commit

Permalink
Test succeeds but not sure if testnet actually starts
Browse files Browse the repository at this point in the history
  • Loading branch information
Jimbo4350 committed May 6, 2024
1 parent 7334a6e commit 187b527
Show file tree
Hide file tree
Showing 3 changed files with 167 additions and 0 deletions.
12 changes: 12 additions & 0 deletions cardano-testnet/src/Testnet/Defaults.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,8 @@ module Testnet.Defaults
, defaultByronProtocolParamsJsonValue
, defaultYamlConfig
, defaultConwayGenesis
, defaultCommitteeVkeyFp
, defaultCommitteeSkeyFp
, defaultDRepVkeyFp
, defaultDRepSkeyFp
, defaultDRepKeyPair
Expand Down Expand Up @@ -504,6 +506,16 @@ defaultGenesisFilepath era =
-- This path is actually generated by create-testnet-data. Don't change it.
eraToString era <> "-genesis.json"

defaultCommitteeVkeyFp
:: Int -- ^ The Committee's index (starts at 1)
-> FilePath
defaultCommitteeVkeyFp n = "committee-keys" </> "committee" <> show n <> ".vkey"

defaultCommitteeSkeyFp
:: Int -- ^ The Committee's index (starts at 1)
-> FilePath
defaultCommitteeSkeyFp n = "committee-keys" </> "committee" <> show n <> ".skey"

-- | The relative path to DRep keys in directories created by cardano-testnet
defaultDRepVkeyFp
:: Int -- ^ The DRep's index (starts at 1)
Expand Down
17 changes: 17 additions & 0 deletions cardano-testnet/src/Testnet/Process/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ module Testnet.Process.Run
, procSubmitApi
, procChairman
, mkExecConfig
, mkExecConfigOffline
, ProcessError(..)
, ExecutableError(..)
) where
Expand Down Expand Up @@ -174,6 +175,22 @@ mkExecConfig tempBaseAbsPath sprocket networkId = do
, H.execConfigCwd = Last $ Just tempBaseAbsPath
}

mkExecConfigOffline :: ()
=> MonadTest m
=> MonadIO m
=> FilePath
-> m ExecConfig
mkExecConfigOffline tempBaseAbsPath = do
env' <- H.evalIO IO.getEnvironment

return H.ExecConfig
{ H.execConfigEnv = Last $ Just
-- The environment must be passed onto child process on Windows in order to
-- successfully start that process.
env'
, H.execConfigCwd = Last $ Just tempBaseAbsPath
}


data ProcessError
= ProcessIOException IOException
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,138 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Testnet.Test.EpochState.Gov.UpdateCommittee
( hprop_epoch_state_update_committee
) where

import Cardano.Api as Api
import Cardano.Api.Error (displayError)
import Cardano.Api.Shelley

import qualified Cardano.Crypto.Hash as L
import qualified Cardano.Ledger.Conway.Genesis as L
import qualified Cardano.Ledger.Conway.Governance as L
import qualified Cardano.Ledger.Conway.Governance as Ledger
import qualified Cardano.Ledger.Credential as L
import qualified Cardano.Ledger.Hashes as L
import qualified Cardano.Ledger.Shelley.LedgerState as L
import Cardano.Testnet

import Prelude

import Control.Monad
import Data.Bifunctor
import qualified Data.ByteString.Char8 as BSC
import qualified Data.Map.Strict as Map
import System.FilePath ((</>))

import Testnet.Components.Configuration
import Testnet.Components.Query
import Testnet.Components.TestWatchdog
import Testnet.Defaults
import qualified Testnet.Process.Cli as P
import qualified Testnet.Process.Run as H
import qualified Testnet.Property.Utils as H
import Testnet.Runtime

import Hedgehog
import qualified Hedgehog as H
import qualified Hedgehog.Extras as H
import qualified Hedgehog.Extras.Stock.IO.Network.Sprocket as IO

-- | Execute me with:
-- @DISABLE_RETRIES=1 cabal test cardano-testnet-test --test-options '-p "/UpdateCommittee/"'@
-- Generate a testnet with a committee defined in the Conway genesis. Add and remove members from the committee
-- in a single governance proposal.
hprop_epoch_state_update_committee :: Property
hprop_epoch_state_update_committee = H.integrationWorkspace "update-committee" $ \tempAbsBasePath' -> runWithDefaultWatchdog_ $ do
-- Start a local test net
conf@Conf { tempAbsPath } <- mkConf tempAbsBasePath'
let tempAbsPath' = unTmpAbsPath tempAbsPath
tempBaseAbsPath = makeTmpBaseAbsPath tempAbsPath

work <- H.createDirectoryIfMissing $ tempAbsPath' </> "work"


let ceo = ConwayEraOnwardsConway
sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
cEra = AnyCardanoEra era
fastTestnetOptions = cardanoDefaultTestnetOptions
{ cardanoEpochLength = 100
, cardanoNodeEra = cEra
}
execConfigOffline <- H.mkExecConfigOffline tempBaseAbsPath

-- Step 1. Define generate and define a committee in the genesis file

-- Create committee cold keys
H.createDirectoryIfMissing_ $ tempAbsPath' </> work </> "committee-keys"
H.forConcurrently_ [1..2] $ \n -> do
H.execCli' execConfigOffline
[ anyEraToString cEra, "governance", "committee"
, "key-gen-cold"
, "--cold-verification-key-file", work </> defaultCommitteeVkeyFp n
, "--cold-signing-key-file", work </> defaultCommitteeSkeyFp n
]

committeeVkey1Fp <- H.noteShow $ work </> defaultCommitteeVkeyFp 1
_committeeSkey1Fp <- H.noteShow $ work </> defaultCommitteeSkeyFp 1
committeeVkey2Fp <- H.noteShow $ work </> defaultCommitteeVkeyFp 2
_committeeSkey2Fp <- H.noteShow $ work </> defaultCommitteeSkeyFp 2

-- Read committee cold keys from disk to put into conway genesis

comKeyHash1Str <- filter (/= '\n') <$> H.execCli' execConfigOffline
[ anyEraToString cEra, "governance", "committee"
, "key-hash"
, "--verification-key-file", committeeVkey1Fp
]

_comKeyHash2Str <- H.execCli' execConfigOffline
[ anyEraToString cEra, "governance", "committee"
, "key-hash"
, "--verification-key-file", committeeVkey2Fp
]

CommitteeColdKeyHash comKeyHash1 <-
H.evalEither
$ deserialiseFromRawBytesHex (AsHash AsCommitteeColdKey)
$ BSC.pack comKeyHash1Str

let comKeyCred1 = L.KeyHashObj comKeyHash1
committeeThreshold = unsafeBoundedRational 0.5
committee = L.Committee (Map.fromList [(comKeyCred1, EpochNo 100)]) committeeThreshold

alonzoGenesis <- evalEither $ first prettyError defaultAlonzoGenesis
(startTime, shelleyGenesis') <- getDefaultShelleyGenesis fastTestnetOptions
let conwayGenesisWithCommittee =
defaultConwayGenesis { L.cgCommittee = committee }
TestnetRuntime
{ testnetMagic
, poolNodes
, wallets=_wallet0:_wallet1:_
, configurationFile
} <- cardanoTestnet
fastTestnetOptions
conf startTime shelleyGenesis'
alonzoGenesis conwayGenesisWithCommittee

poolNode1 <- H.headM poolNodes
poolSprocket1 <- H.noteShow $ nodeSprocket $ poolRuntime poolNode1
_execConfig <- H.mkExecConfig tempBaseAbsPath poolSprocket1 testnetMagic

let socketName' = IO.sprocketName poolSprocket1
socketBase = IO.sprocketBase poolSprocket1 -- /tmp
socketPath = socketBase </> socketName'

_epochStateView <- getEpochStateView (File configurationFile) (File socketPath)

H.note_ $ "Sprocket: " <> show poolSprocket1
H.note_ $ "Abs path: " <> tempAbsBasePath'
H.note_ $ "Socketpath: " <> socketPath
return ()

0 comments on commit 187b527

Please sign in to comment.