11{-# LANGUAGE BangPatterns #-}
22{-# LANGUAGE DataKinds #-}
3+ {-# LANGUAGE FlexibleContexts #-}
34{-# LANGUAGE NamedFieldPuns #-}
45{-# LANGUAGE OverloadedStrings #-}
56{-# LANGUAGE ScopedTypeVariables #-}
@@ -10,28 +11,29 @@ module Cardano.Testnet.Test.LedgerEvents.Gov.PredefinedAbstainDRep
1011 ) where
1112
1213import Cardano.Api as Api
14+ import Cardano.Api.Eon.ShelleyBasedEra (ShelleyLedgerEra )
1315import Cardano.Api.Error (displayError )
1416
17+ import Cardano.Ledger.Conway.Core (ppNOptL )
18+ import Cardano.Ledger.Conway.Governance (ConwayGovState , cgsCurPParamsL )
19+ import Cardano.Ledger.Core (EraPParams )
1520import Cardano.Testnet
1621
1722import Prelude
1823
1924import Control.Monad (void )
2025import Control.Monad.Catch (MonadCatch )
21- import qualified Data.Aeson as Aeson
22- import qualified Data.Aeson.Lens as AL
23- import Data.ByteString.Lazy.Char8 (pack )
2426import Data.String (fromString )
2527import qualified Data.Text as Text
2628import Data.Word (Word32 )
2729import GHC.Stack (HasCallStack , callStack )
28- import Lens.Micro ((^? ) )
30+ import Lens.Micro ((^. ) )
2931import System.FilePath ((</>) )
3032
3133import Testnet.Components.DReps (createCertificatePublicationTxBody , createVotingTxBody ,
3234 generateVoteFiles , retrieveTransactionId , signTx , submitTx )
3335import Testnet.Components.Query (EpochStateView , findLargestUtxoForPaymentKey ,
34- getCurrentEpochNo , getEpochStateView , getMinDRepDeposit )
36+ getCurrentEpochNo , getEpochStateView , getGovState , getMinDRepDeposit )
3537import Testnet.Defaults (defaultDRepKeyPair , defaultDelegatorStakeKeyPair )
3638import qualified Testnet.Process.Cli as P
3739import qualified Testnet.Process.Run as H
@@ -100,7 +102,7 @@ hprop_check_predefined_abstain_drep = H.integrationWorkspace "test-activity" $ \
100102
101103 gov <- H. createDirectoryIfMissing $ work </> " governance"
102104
103- initialDesiredNumberOfPools <- getDesiredPoolNumberValue execConfig
105+ initialDesiredNumberOfPools <- getDesiredPoolNumberValue epochStateView ceo
104106
105107 let newNumberOfDesiredPools = initialDesiredNumberOfPools + 1
106108
@@ -206,7 +208,7 @@ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socket
206208 H. note_ $ " Epoch after \" " <> prefix <> " \" prop: " <> show epochAfterProp
207209
208210 void $ waitUntilEpoch (File configurationFile) (File socketPath) (EpochNo (epochAfterProp + fromIntegral epochsToWait))
209- desiredPoolNumberAfterProp <- getDesiredPoolNumberValue execConfig
211+ desiredPoolNumberAfterProp <- getDesiredPoolNumberValue epochStateView ceo
210212
211213 desiredPoolNumberAfterProp === expected
212214
@@ -346,17 +348,11 @@ voteChangeProposal execConfig epochStateView sbe work prefix
346348-- decentralization and efficiency and the spec suggest it should be between 100 an 1000.
347349-- Changing this parameter will inderectly affect how easy it is to saturate a pool in order to
348350-- incentivize that the number of SPOs states close to the parameter value.
349- getDesiredPoolNumberValue :: (MonadTest m , MonadCatch m , MonadIO m ) => H. ExecConfig -> m Integer
350- getDesiredPoolNumberValue execConfig = do
351- govStateString <- H. execCli' execConfig
352- [ " conway" , " query" , " gov-state"
353- , " --volatile-tip"
354- ]
355-
356- govStateJSON <- H. nothingFail (Aeson. decode (pack govStateString) :: Maybe Aeson. Value )
357- let mTargetPoolNum :: Maybe Integer
358- mTargetPoolNum = govStateJSON
359- ^? AL. key " currentPParams"
360- . AL. key " stakePoolTargetNum"
361- . AL. _Integer
362- evalMaybe mTargetPoolNum
351+ getDesiredPoolNumberValue :: (EraPParams (ShelleyLedgerEra era ), H. MonadAssertion m , MonadTest m , MonadIO m )
352+ => EpochStateView
353+ -> ConwayEraOnwards era
354+ -> m Integer
355+ getDesiredPoolNumberValue epochStateView ceo = do
356+ govState :: ConwayGovState era <- getGovState epochStateView ceo
357+ return $ toInteger $ govState ^. cgsCurPParamsL
358+ . ppNOptL
0 commit comments