Skip to content

Commit

Permalink
Update signal of Enact rule to be new type EnactSignal
Browse files Browse the repository at this point in the history
which contains `GovActionId` in addition to `GovAction`
  • Loading branch information
teodanciu committed Aug 29, 2023
1 parent 74d4415 commit 04a544c
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 7 deletions.
11 changes: 9 additions & 2 deletions eras/conway/impl/src/Cardano/Ledger/Conway/Rules/Enact.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@

module Cardano.Ledger.Conway.Rules.Enact (
ConwayENACT,
EnactSignal (..),
EnactState (..),
EnactPredFailure (..),
) where
Expand All @@ -22,6 +23,7 @@ import Cardano.Ledger.Conway.Era (ConwayENACT)
import Cardano.Ledger.Conway.Governance (
EnactState (..),
GovAction (..),
GovActionId (..),
)
import Cardano.Ledger.Rules.ValidationMode (Inject (..), runTest)
import Cardano.Ledger.Val (Val (..))
Expand All @@ -40,10 +42,15 @@ data EnactPredFailure era
= EnactTreasuryInsufficientFunds !(Map (RewardAcnt (EraCrypto era)) Coin) !Coin
deriving (Show, Eq)

data EnactSignal era = EnactSignal
{ esGovActionId :: !(GovActionId (EraCrypto era))
, esGovAction :: !(GovAction era)
}

instance EraGov era => STS (ConwayENACT era) where
type Environment (ConwayENACT era) = ()
type PredicateFailure (ConwayENACT era) = EnactPredFailure era
type Signal (ConwayENACT era) = GovAction era
type Signal (ConwayENACT era) = EnactSignal era
type State (ConwayENACT era) = EnactState era
type BaseM (ConwayENACT era) = ShelleyBase

Expand All @@ -52,7 +59,7 @@ instance EraGov era => STS (ConwayENACT era) where

enactmentTransition :: forall era. EraPParams era => TransitionRule (ConwayENACT era)
enactmentTransition = do
TRC ((), st, act) <- judgmentContext
TRC ((), st, EnactSignal _ act) <- judgmentContext

case act of
ParameterChange _prevGovActionId ppup -> pure $ st {ensPParams = newPP}
Expand Down
12 changes: 7 additions & 5 deletions eras/conway/impl/src/Cardano/Ledger/Conway/Rules/Ratify.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import Cardano.Ledger.Conway.Governance (
RatifyState (..),
Vote (..),
)
import Cardano.Ledger.Conway.Rules.Enact (EnactPredFailure, EnactState (..))
import Cardano.Ledger.Conway.Rules.Enact (EnactPredFailure, EnactSignal (..), EnactState (..))
import Cardano.Ledger.Core
import Cardano.Ledger.Credential (Credential (..))
import Cardano.Ledger.Keys (KeyRole (..))
Expand Down Expand Up @@ -73,7 +73,7 @@ instance
, Embed (EraRule "ENACT" era) (ConwayRATIFY era)
, State (EraRule "ENACT" era) ~ EnactState era
, Environment (EraRule "ENACT" era) ~ ()
, Signal (EraRule "ENACT" era) ~ GovAction era
, Signal (EraRule "ENACT" era) ~ EnactSignal era
) =>
STS (ConwayRATIFY era)
where
Expand Down Expand Up @@ -191,7 +191,7 @@ ratifyTransition ::
( Embed (EraRule "ENACT" era) (ConwayRATIFY era)
, State (EraRule "ENACT" era) ~ EnactState era
, Environment (EraRule "ENACT" era) ~ ()
, Signal (EraRule "ENACT" era) ~ GovAction era
, Signal (EraRule "ENACT" era) ~ EnactSignal era
, Era era
) =>
TransitionRule (ConwayRATIFY era)
Expand All @@ -205,13 +205,15 @@ ratifyTransition = do

case rsig of
ast :<| sigs -> do
let GovActionState {gasAction, gasExpiresAfter} = ast
let GovActionState {gasId, gasAction, gasExpiresAfter} = ast
if spoAccepted env ast
&& dRepAccepted env ast dRepThreshold
&& prevActionAsExpected gasAction (ensPrevGovActionIds rsEnactState)
then do
-- Update ENACT state with the governance action that was ratified
es <- trans @(EraRule "ENACT" era) $ TRC ((), rsEnactState, gasAction)
es <-
trans @(EraRule "ENACT" era) $
TRC ((), rsEnactState, EnactSignal gasId gasAction)
let st' =
st
{ rsEnactState = es
Expand Down

0 comments on commit 04a544c

Please sign in to comment.