Skip to content

Commit

Permalink
Fixes required by rebasing
Browse files Browse the repository at this point in the history
  • Loading branch information
palas committed May 3, 2024
1 parent 350eec1 commit fda961e
Show file tree
Hide file tree
Showing 6 changed files with 20 additions and 17 deletions.
14 changes: 8 additions & 6 deletions cardano-testnet/src/Testnet/EpochStateProcessing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,10 +5,10 @@ module Testnet.EpochStateProcessing
, findCondition
) where

import Cardano.Api (AnyNewEpochState (..), ConwayEra, EpochNo, File (File),
FoldBlocksError, LedgerStateCondition (..), MonadIO, ShelleyBasedEra,
ValidationMode (FullValidation), foldEpochState, runExceptT,
shelleyBasedEraConstraints)
import Cardano.Api (AnyNewEpochState (..), ConwayEra, ConwayEraOnwards, EpochNo,
File (File), FoldBlocksError, LedgerStateCondition (..), MonadIO,
ValidationMode (FullValidation), conwayEraOnwardsToShelleyBasedEra,
foldEpochState, runExceptT, shelleyBasedEraConstraints)
import qualified Cardano.Api as Api
import Cardano.Api.Ledger (GovActionId (..))
import qualified Cardano.Api.Ledger as L
Expand Down Expand Up @@ -58,11 +58,13 @@ findCondition epochStateFoldFunc configurationFile socketPath maxEpochNo = withF
Just x -> put (Just x) >> pure ConditionMet
Nothing -> pure ConditionNotMet

maybeExtractGovernanceActionIndex :: ShelleyBasedEra ConwayEra -- ^ The era in which the test runs
maybeExtractGovernanceActionIndex :: ()
=> ConwayEraOnwards ConwayEra -- ^ The era in which the test runs
-> Api.TxId
-> AnyNewEpochState
-> Maybe Word32
maybeExtractGovernanceActionIndex sbe txid (AnyNewEpochState actualEra newEpochState) =
maybeExtractGovernanceActionIndex ceo txid (AnyNewEpochState actualEra newEpochState) =
let sbe = conwayEraOnwardsToShelleyBasedEra ceo in
case testEquality sbe actualEra of
Just Refl -> do
let proposals = shelleyBasedEraConstraints sbe newEpochState
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -269,7 +269,7 @@ makeActivityChangeProposal execConfig epochStateView configurationFile socketPat

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
(unFile configurationFile)
(unFile socketPath)
(EpochNo timeout)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,8 @@ hprop_ledger_events_info_action = H.integrationRetryWorkspace 0 "info-hash" $ \t

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

let sbe = ShelleyBasedEraConway
let ceo = ConwayEraOnwardsConway
sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
fastTestnetOptions = cardanoDefaultTestnetOptions
{ cardanoEpochLength = 100
Expand Down Expand Up @@ -149,7 +150,7 @@ hprop_ledger_events_info_action = H.integrationRetryWorkspace 0 "info-hash" $ \t
, "--tx-file", txbodySignedFp
]

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString txidString))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString txidString))
configurationFile
socketPath
(EpochNo 10)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ import Prelude

import Control.Monad (void)
import Control.Monad.Catch (MonadCatch)
import Data.Data (Typeable)
import Data.String (fromString)
import qualified Data.Text as Text
import Data.Word (Word32)
Expand Down Expand Up @@ -316,7 +317,7 @@ makeDesiredPoolNumberChangeProposal execConfig epochStateView configurationFile

(EpochNo curEpoch) <- getCurrentEpochNo epochStateView

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
(unFile configurationFile)
(unFile socketPath)
(EpochNo $ curEpoch + 10)
Expand All @@ -342,11 +343,10 @@ type DefaultSPOVote = (String, Int)
-- | Create and issue votes for (or against) a government proposal with default
-- Delegate Representative (DReps created by 'cardanoTestnetDefault') and
-- default Stake Pool Operatorsusing using @cardano-cli@.
voteChangeProposal :: (MonadTest m, MonadIO m, MonadCatch m, H.MonadAssertion m)
voteChangeProposal :: (Typeable era, MonadTest m, MonadIO m, MonadCatch m, H.MonadAssertion m)
=> H.ExecConfig -- ^ Specifies the CLI execution configuration.
-> EpochStateView -- ^ Current epoch state view for transaction building. It can be obtained
-- using the 'getEpochStateView' function.
-> ConwayEraOnwards ConwayEra -- ^ The @ConwayEraOnwards@ witness for the Conway era.
-> ConwayEraOnwards era -- ^ The @ConwayEraOnwards@ witness for the current era.
-> FilePath -- ^ Base directory path where the subdirectory with the intermediate files will be created.
-> String -- ^ Name for the subdirectory that will be created for storing the intermediate files.
-> String -- ^ Transaction id of the governance action to vote.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -302,7 +302,7 @@ makeUpdateConstitutionalCommitteeProposal execConfig epochStateView configuratio

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
(unFile configurationFile)
(unFile socketPath)
(EpochNo 10)
Expand Down Expand Up @@ -441,7 +441,7 @@ makeNoConfidenceProposal execConfig epochStateView configurationFile socketPath

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
(unFile configurationFile)
(unFile socketPath)
(EpochNo 30)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -172,7 +172,7 @@ hprop_ledger_events_propose_new_constitution = H.integrationWorkspace "propose-n

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
configurationFile
socketPath
(EpochNo 10)
Expand Down Expand Up @@ -205,7 +205,7 @@ hprop_ledger_events_propose_new_constitution = H.integrationWorkspace "propose-n
(File configurationFile)
(File socketPath)
FullValidation
(EpochNo 10)
(EpochNo 30)
()
(\epochState _ _ -> foldBlocksCheckConstitutionWasRatified constitutionHash constitutionScriptHash epochState)

Expand Down

0 comments on commit fda961e

Please sign in to comment.