1
1
{-# LANGUAGE BangPatterns #-}
2
2
{-# LANGUAGE DataKinds #-}
3
+ {-# LANGUAGE FlexibleContexts #-}
3
4
{-# LANGUAGE NamedFieldPuns #-}
4
5
{-# LANGUAGE OverloadedStrings #-}
5
6
{-# LANGUAGE ScopedTypeVariables #-}
@@ -10,28 +11,29 @@ module Cardano.Testnet.Test.LedgerEvents.Gov.PredefinedAbstainDRep
10
11
) where
11
12
12
13
import Cardano.Api as Api
14
+ import Cardano.Api.Eon.ShelleyBasedEra (ShelleyLedgerEra )
13
15
import Cardano.Api.Error (displayError )
14
16
17
+ import Cardano.Ledger.Conway.Core (ppNOptL )
18
+ import Cardano.Ledger.Conway.Governance (ConwayGovState , cgsCurPParamsL )
19
+ import Cardano.Ledger.Core (EraPParams )
15
20
import Cardano.Testnet
16
21
17
22
import Prelude
18
23
19
24
import Control.Monad (void )
20
25
import 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 )
24
26
import Data.String (fromString )
25
27
import qualified Data.Text as Text
26
28
import Data.Word (Word32 )
27
29
import GHC.Stack (HasCallStack , callStack )
28
- import Lens.Micro ((^? ) )
30
+ import Lens.Micro ((^. ) )
29
31
import System.FilePath ((</>) )
30
32
31
33
import Testnet.Components.DReps (createCertificatePublicationTxBody , createVotingTxBody ,
32
34
generateVoteFiles , retrieveTransactionId , signTx , submitTx )
33
35
import Testnet.Components.Query (EpochStateView , findLargestUtxoForPaymentKey ,
34
- getCurrentEpochNo , getEpochStateView , getMinDRepDeposit )
36
+ getCurrentEpochNo , getEpochStateView , getGovState , getMinDRepDeposit )
35
37
import Testnet.Defaults (defaultDRepKeyPair , defaultDelegatorStakeKeyPair )
36
38
import qualified Testnet.Process.Cli as P
37
39
import qualified Testnet.Process.Run as H
@@ -100,7 +102,7 @@ hprop_check_predefined_abstain_drep = H.integrationWorkspace "test-activity" $ \
100
102
101
103
gov <- H. createDirectoryIfMissing $ work </> " governance"
102
104
103
- initialDesiredNumberOfPools <- getDesiredPoolNumberValue execConfig
105
+ initialDesiredNumberOfPools <- getDesiredPoolNumberValue epochStateView ceo
104
106
105
107
let newNumberOfDesiredPools = initialDesiredNumberOfPools + 1
106
108
@@ -206,7 +208,7 @@ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socket
206
208
H. note_ $ " Epoch after \" " <> prefix <> " \" prop: " <> show epochAfterProp
207
209
208
210
void $ waitUntilEpoch (File configurationFile) (File socketPath) (EpochNo (epochAfterProp + fromIntegral epochsToWait))
209
- desiredPoolNumberAfterProp <- getDesiredPoolNumberValue execConfig
211
+ desiredPoolNumberAfterProp <- getDesiredPoolNumberValue epochStateView ceo
210
212
211
213
desiredPoolNumberAfterProp === expected
212
214
@@ -346,17 +348,11 @@ voteChangeProposal execConfig epochStateView sbe work prefix
346
348
-- decentralization and efficiency and the spec suggest it should be between 100 an 1000.
347
349
-- Changing this parameter will inderectly affect how easy it is to saturate a pool in order to
348
350
-- 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