Skip to content

Commit

Permalink
Used getGovState instead of calling cardano-clì
Browse files Browse the repository at this point in the history
  • Loading branch information
palas committed May 3, 2024
1 parent 3f68f04 commit 9bf8450
Showing 1 changed file with 17 additions and 21 deletions.
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand All @@ -10,28 +11,29 @@ module Cardano.Testnet.Test.LedgerEvents.Gov.PredefinedAbstainDRep
) where

import Cardano.Api as Api
import Cardano.Api.Eon.ShelleyBasedEra (ShelleyLedgerEra)
import Cardano.Api.Error (displayError)

import Cardano.Ledger.Conway.Core (ppNOptL)
import Cardano.Ledger.Conway.Governance (ConwayGovState, cgsCurPParamsL)
import Cardano.Ledger.Core (EraPParams)
import Cardano.Testnet

import Prelude

import Control.Monad (void)
import Control.Monad.Catch (MonadCatch)
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Lens as AL
import Data.ByteString.Lazy.Char8 (pack)
import Data.String (fromString)
import qualified Data.Text as Text
import Data.Word (Word32)
import GHC.Stack (HasCallStack, callStack)
import Lens.Micro ((^?))
import Lens.Micro ((^.))
import System.FilePath ((</>))

import Testnet.Components.DReps (createCertificatePublicationTxBody, createVotingTxBody,
generateVoteFiles, retrieveTransactionId, signTx, submitTx)
import Testnet.Components.Query (EpochStateView, findLargestUtxoForPaymentKey,
getCurrentEpochNo, getEpochStateView, getMinDRepDeposit)
getCurrentEpochNo, getEpochStateView, getGovState, getMinDRepDeposit)
import Testnet.Defaults (defaultDRepKeyPair, defaultDelegatorStakeKeyPair)
import qualified Testnet.Process.Cli as P
import qualified Testnet.Process.Run as H
Expand Down Expand Up @@ -100,7 +102,7 @@ hprop_check_predefined_abstain_drep = H.integrationWorkspace "test-activity" $ \

gov <- H.createDirectoryIfMissing $ work </> "governance"

initialDesiredNumberOfPools <- getDesiredPoolNumberValue execConfig
initialDesiredNumberOfPools <- getDesiredPoolNumberValue epochStateView ceo

let newNumberOfDesiredPools = initialDesiredNumberOfPools + 1

Expand Down Expand Up @@ -206,7 +208,7 @@ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socket
H.note_ $ "Epoch after \"" <> prefix <> "\" prop: " <> show epochAfterProp

void $ waitUntilEpoch (File configurationFile) (File socketPath) (EpochNo (epochAfterProp + fromIntegral epochsToWait))
desiredPoolNumberAfterProp <- getDesiredPoolNumberValue execConfig
desiredPoolNumberAfterProp <- getDesiredPoolNumberValue epochStateView ceo

desiredPoolNumberAfterProp === expected

Expand Down Expand Up @@ -346,17 +348,11 @@ voteChangeProposal execConfig epochStateView sbe work prefix
-- decentralization and efficiency and the spec suggest it should be between 100 an 1000.
-- Changing this parameter will inderectly affect how easy it is to saturate a pool in order to
-- incentivize that the number of SPOs states close to the parameter value.
getDesiredPoolNumberValue :: (MonadTest m, MonadCatch m, MonadIO m) => H.ExecConfig -> m Integer
getDesiredPoolNumberValue execConfig = do
govStateString <- H.execCli' execConfig
[ "conway", "query", "gov-state"
, "--volatile-tip"
]

govStateJSON <- H.nothingFail (Aeson.decode (pack govStateString) :: Maybe Aeson.Value)
let mTargetPoolNum :: Maybe Integer
mTargetPoolNum = govStateJSON
^? AL.key "currentPParams"
. AL.key "stakePoolTargetNum"
. AL._Integer
evalMaybe mTargetPoolNum
getDesiredPoolNumberValue :: (EraPParams (ShelleyLedgerEra era), H.MonadAssertion m, MonadTest m, MonadIO m)
=> EpochStateView
-> ConwayEraOnwards era
-> m Integer
getDesiredPoolNumberValue epochStateView ceo = do
govState :: ConwayGovState era <- getGovState epochStateView ceo
return $ toInteger $ govState ^. cgsCurPParamsL
. ppNOptL

0 comments on commit 9bf8450

Please sign in to comment.