Skip to content

Commit

Permalink
Add unit test which shows that the protocol version of the devnet is 10.
Browse files Browse the repository at this point in the history
  • Loading branch information
koslambrou committed Nov 8, 2024
1 parent 3a7b90c commit 11f0a75
Show file tree
Hide file tree
Showing 6 changed files with 62 additions and 33 deletions.
8 changes: 8 additions & 0 deletions src/base/lib/Convex/NodeQueries.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ module Convex.NodeQueries(
queryEpoch,
queryLocalState,
queryProtocolParameters,
queryProtocolParametersUpdate,
queryStakePools,
queryStakeAddresses,
queryUTxOFilter
Expand Down Expand Up @@ -267,6 +268,13 @@ queryProtocolParameters :: LocalNodeConnectInfo -> IO (PParams StandardConway)
queryProtocolParameters connectInfo = runEraQuery connectInfo $
EraQuery{eqQuery = CAPI.QueryProtocolParameters, eqResult = id}

-- | Get all the protocol parameter updates from the local cardano node
-- Throws 'QueryException' if the node's era is not conway or if the connection
-- to the node cannot be acquired
queryProtocolParametersUpdate :: LocalNodeConnectInfo -> IO (Map (CAPI.Hash CAPI.GenesisKey) CAPI.ProtocolParametersUpdate)
queryProtocolParametersUpdate connectInfo = runEraQuery @CAPI.ConwayEra connectInfo $
EraQuery{eqQuery = CAPI.QueryProtocolParametersUpdate, eqResult = id}

-- | Get the stake and the IDs of the stake pool for a set of stake credentials
-- Throws 'QueryException' if the node's era is not supported or if the connection
-- to the node cannot be acquired
Expand Down
7 changes: 3 additions & 4 deletions src/devnet/config/devnet/cardano-node.json
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,8 @@
"LastKnownBlockVersion-Major": 6,
"LastKnownBlockVersion-Minor": 0,

"ExperimentalHardForksEnabled": true,
"ExperimentalProtocolsEnabled": true,
"TestShelleyHardForkAtEpoch": 0,
"TestAllegraHardForkAtEpoch": 0,
"TestMaryHardForkAtEpoch": 0,
Expand Down Expand Up @@ -74,8 +76,5 @@
"mapSubtrace": {
"cardano.node.metrics": { "subtrace": "Neutral" }
}
},

"ExperimentalHardForksEnabled": true,
"ExperimentalProtocolsEnabled": true
}
}
2 changes: 1 addition & 1 deletion src/devnet/config/devnet/genesis-shelley.json
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@
"nOpt": 100,
"poolDeposit": 0,
"protocolVersion": {
"major": 7,
"major": 2,
"minor": 0
},
"rho": 0.003,
Expand Down
4 changes: 3 additions & 1 deletion src/devnet/convex-devnet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,6 @@ library
build-depends:
base >= 4.14.0
, aeson
, lens-aeson
, text
, time
, bytestring
Expand Down Expand Up @@ -108,6 +107,9 @@ test-suite convex-devnet-test
, tasty-hunit
, convex-devnet
, convex-base
, convex-node-client
, ouroboros-consensus-cardano
, ouroboros-consensus-protocol
, cardano-api
, contra-tracer
, cardano-ledger-api
Expand Down
10 changes: 1 addition & 9 deletions src/devnet/lib/Convex/Devnet/CardanoNode/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@ module Convex.Devnet.CardanoNode.Types (
defaultStakePoolNodeParams,
-- * Genesis config changes
GenesisConfigChanges (..),
forkIntoConwayInEpoch,
allowLargeTransactions,
setEpochLength
) where
Expand All @@ -27,13 +26,11 @@ import Cardano.Ledger.BaseTypes (EpochSize)
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Shelley.API (Coin)
import Cardano.Ledger.Shelley.Genesis (ShelleyGenesis (..))
import Control.Lens (over, set)
import Control.Lens (over)
import Data.Aeson (FromJSON, ToJSON)
import qualified Data.Aeson as Aeson
import Data.Aeson.Lens (atKey)
import Data.Ratio ((%))
import GHC.Generics (Generic)
import Numeric.Natural (Natural)
import Ouroboros.Consensus.Shelley.Eras (ShelleyEra, StandardCrypto)

type Port = Int
Expand Down Expand Up @@ -122,11 +119,6 @@ instance Semigroup GenesisConfigChanges where
instance Monoid GenesisConfigChanges where
mempty = GenesisConfigChanges id id id id

-- | Set the 'TestConwayHardForkAtEpoch' field to the given value (can be 0)
forkIntoConwayInEpoch :: Natural -> GenesisConfigChanges
forkIntoConwayInEpoch n =
mempty{ cfNodeConfig = set (atKey "TestConwayHardForkAtEpoch") (Just $ Aeson.toJSON n) }

{-| Change the alonzo genesis config to allow transactions with up to twice the normal size
-}
allowLargeTransactions :: GenesisConfigChanges
Expand Down
64 changes: 46 additions & 18 deletions src/devnet/test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,15 +4,19 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE GADTs #-}
module Main where

import qualified Cardano.Api as C
import qualified Cardano.Api.Shelley as C
import Cardano.Ledger.Api.PParams (ppMaxTxSizeL)
import qualified Cardano.Api.Ledger as L
import Data.IORef (newIORef, modifyIORef, readIORef)
import Cardano.Ledger.Api.PParams qualified as L
import Cardano.Ledger.Slot (EpochSize (..))
import qualified Cardano.Ledger.Block as Ledger
import Control.Concurrent (threadDelay)
import Control.Lens (view)
import Control.Monad (unless)
import Control.Monad (void, unless)
import Control.Monad.Except (runExceptT)
import Control.Tracer (Tracer)
import Convex.Devnet.CardanoNode (NodeLog (..),
Expand All @@ -27,8 +31,7 @@ import Convex.Devnet.CardanoNode.Types (GenesisConfigChanges (..),
StakePoolNodeParams (..),
allowLargeTransactions,
defaultPortsConfig,
defaultStakePoolNodeParams,
forkIntoConwayInEpoch)
defaultStakePoolNodeParams)
import Convex.Devnet.Logging (contramap, showLogsOnFailure,
traceWith)
import Convex.Devnet.Utils (failAfter, failure,
Expand All @@ -54,14 +57,18 @@ import System.FilePath ((</>))
import Test.Tasty (defaultMain, testGroup)
import Test.Tasty.HUnit (assertBool, assertEqual,
testCase)
import Convex.NodeClient.Types (runNodeClient)
import Convex.NodeClient.Fold (foldClient, LedgerStateArgs(NoLedgerStateArgs))
import Ouroboros.Consensus.Shelley.Ledger.Block qualified as Consensus
import Ouroboros.Consensus.Protocol.Praos.Header qualified as Consensus

main :: IO ()
main = do
setLocaleEncoding utf8
defaultMain $ testGroup "test"
[ testCase "cardano-node is available" checkCardanoNode
, testCase "start local node" startLocalNode
, testCase "transition to conway era" transitionToConway
, testCase "check transition to conway era and protocol version 10" checkTransitionToConway
, testCase "make a payment" makePayment
, testCase "start local stake pool node" startLocalStakePoolNode
, testCase "stake pool registration" registeredStakePoolNode
Expand All @@ -83,21 +90,42 @@ startLocalNode = do
showLogsOnFailure $ \tr -> do
failAfter 5 $
withTempDir "cardano-cluster" $ \tmp -> do
withCardanoNodeDevnet tr tmp $ \RunningNode{rnNodeSocket, rnNodeConfigFile, rnConnectInfo} -> do
withCardanoNodeDevnet tr tmp $ \RunningNode{rnNodeSocket, rnNodeConfigFile} -> do
runExceptT (loadConnectInfo rnNodeConfigFile rnNodeSocket) >>= \case
Left err -> failure (show err)
Right{} -> do
Queries.queryEra rnConnectInfo
>>= assertBool "Should be in conway era" . (==) (C.anyCardanoEra C.ConwayEra)
Right{} -> pure ()

checkTransitionToConway :: IO ()
checkTransitionToConway = do
showLogsOnFailure $ \tr -> do
failAfter 5 $
withTempDir "cardano-cluster" $ \tmp -> do
withCardanoNodeDevnet (contramap TLNode tr) tmp $ \runningNode@RunningNode{rnConnectInfo, rnNodeSocket, rnNodeConfigFile} -> do
Queries.queryEra rnConnectInfo >>= assertEqual "Should be in conway era" (C.anyCardanoEra C.ConwayEra)
let lovelacePerUtxo = 100_000_000
numUtxos = 10
void $ W.createSeededWallet (contramap TLWallet tr) runningNode numUtxos lovelacePerUtxo
majorProtVersionsRef <- newIORef []
res <- C.liftIO $ runExceptT $ runNodeClient rnNodeConfigFile rnNodeSocket $ \_localNodeConnectInfo env -> do
pure $ foldClient () NoLedgerStateArgs env $ \_catchingUp _ _ bim -> do
case bim of
(C.BlockInMode C.ConwayEra
(C.ShelleyBlock C.ShelleyBasedEraConway
(Consensus.ShelleyBlock
(Ledger.Block (Consensus.Header hb _) _) _))) -> do
modifyIORef majorProtVersionsRef $ \majorProtVersions ->
L.pvMajor (Consensus.hbProtVer hb) : majorProtVersions
pure Nothing
(C.BlockInMode _ _block) -> do
failure "Block should be a ShelleyBlock in Conway era"
case res of
Left err -> failure $ show err
Right () -> do
majorProtVersions <- readIORef majorProtVersionsRef
expectedVersion <- L.mkVersion (10 :: Integer)
assertBool "Should have correct conway era protocol version" $
not (null majorProtVersions) && all (== expectedVersion) majorProtVersions

transitionToConway :: IO ()
transitionToConway = do
showLogsOnFailure $ \tr -> do
failAfter 5 $
withTempDir "cardano-cluster" $ \tmp -> do
withCardanoNodeDevnetConfig tr tmp (forkIntoConwayInEpoch 0) defaultPortsConfig $ \RunningNode{rnConnectInfo} -> do
Queries.queryEra rnConnectInfo
>>= assertBool "Should be in conway era" . (==) (C.anyCardanoEra C.ConwayEra)

startLocalStakePoolNode :: IO ()
startLocalStakePoolNode = do
Expand Down Expand Up @@ -211,7 +239,7 @@ runWalletServer =

changeMaxTxSize :: IO ()
changeMaxTxSize =
let getMaxTxSize = fmap (view ppMaxTxSizeL) . queryProtocolParameters . rnConnectInfo in
let getMaxTxSize = fmap (view L.ppMaxTxSizeL) . queryProtocolParameters . rnConnectInfo in
showLogsOnFailure $ \tr -> do
withTempDir "cardano-cluster" $ \tmp -> do
standardTxSize <- withCardanoNodeDevnet (contramap TLNode tr) tmp getMaxTxSize
Expand Down

0 comments on commit 11f0a75

Please sign in to comment.