Skip to content

Commit

Permalink
Rename CommitteeCert into a GovCert (#3585)
Browse files Browse the repository at this point in the history
* Rename CommitteeCert into a GovCert
  • Loading branch information
lehins authored Jul 28, 2023
1 parent b9754a1 commit 454a7d3
Show file tree
Hide file tree
Showing 8 changed files with 48 additions and 40 deletions.
3 changes: 3 additions & 0 deletions eras/conway/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,9 @@
* Change `GovernanceActionDoesNotExist` to `GovernanceActionsDoNotExist`, which now
reports all actions as a set, rather than one action per each individual failure.
* Type of `gpVotingProcedures` in `GovernanceProcedures` was aslo changed to `GovernanceProcedures`
* Rename:
* `ConwayCommitteeCert` -> `ConwayGovCert`
* `ConwayTxCertCommittee` -> `ConwayTxCertGov`

## 1.6.3.0

Expand Down
8 changes: 4 additions & 4 deletions eras/conway/impl/src/Cardano/Ledger/Conway/Rules/Cert.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ import Cardano.Ledger.Conway.Core
import Cardano.Ledger.Conway.Era (ConwayCERT, ConwayDELEG, ConwayGOVCERT, ConwayPOOL)
import Cardano.Ledger.Conway.Rules.Deleg (ConwayDelegPredFailure (..))
import Cardano.Ledger.Conway.Rules.GovCert (ConwayGovCertPredFailure)
import Cardano.Ledger.Conway.TxCert (ConwayCommitteeCert, ConwayDelegCert, ConwayTxCert (..))
import Cardano.Ledger.Conway.TxCert (ConwayDelegCert, ConwayGovCert, ConwayTxCert (..))
import Cardano.Ledger.Shelley.API (
CertState (..),
DState,
Expand Down Expand Up @@ -103,7 +103,7 @@ instance
, Environment (EraRule "GOVCERT" era) ~ PParams era
, Signal (EraRule "DELEG" era) ~ ConwayDelegCert (EraCrypto era)
, Signal (EraRule "POOL" era) ~ PoolCert (EraCrypto era)
, Signal (EraRule "GOVCERT" era) ~ ConwayCommitteeCert (EraCrypto era)
, Signal (EraRule "GOVCERT" era) ~ ConwayGovCert (EraCrypto era)
, Embed (EraRule "DELEG" era) (ConwayCERT era)
, Embed (EraRule "POOL" era) (ConwayCERT era)
, Embed (EraRule "GOVCERT" era) (ConwayCERT era)
Expand All @@ -130,7 +130,7 @@ certTransition ::
, Environment (EraRule "GOVCERT" era) ~ PParams era
, Signal (EraRule "DELEG" era) ~ ConwayDelegCert (EraCrypto era)
, Signal (EraRule "POOL" era) ~ PoolCert (EraCrypto era)
, Signal (EraRule "GOVCERT" era) ~ ConwayCommitteeCert (EraCrypto era)
, Signal (EraRule "GOVCERT" era) ~ ConwayGovCert (EraCrypto era)
, Embed (EraRule "DELEG" era) (ConwayCERT era)
, Embed (EraRule "POOL" era) (ConwayCERT era)
, Embed (EraRule "GOVCERT" era) (ConwayCERT era)
Expand All @@ -147,7 +147,7 @@ certTransition = do
ConwayTxCertPool poolCert -> do
newPState <- trans @(EraRule "POOL" era) $ TRC (PoolEnv slot pp, certPState, poolCert)
pure $ cState {certPState = newPState}
ConwayTxCertCommittee govCert -> do
ConwayTxCertGov govCert -> do
newVState <- trans @(EraRule "GOVCERT" era) $ TRC (pp, certVState, govCert)
pure $ cState {certVState = newVState}

Expand Down
6 changes: 3 additions & 3 deletions eras/conway/impl/src/Cardano/Ledger/Conway/Rules/GovCert.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ import Cardano.Ledger.Binary.Coders
import Cardano.Ledger.CertState (VState (..))
import Cardano.Ledger.Coin (Coin)
import Cardano.Ledger.Conway.Era (ConwayGOVCERT)
import Cardano.Ledger.Conway.TxCert (ConwayCommitteeCert (..))
import Cardano.Ledger.Conway.TxCert (ConwayGovCert (..))
import Cardano.Ledger.Core (Era (EraCrypto), EraPParams, EraRule, PParams)
import Cardano.Ledger.Credential (Credential)
import Cardano.Ledger.Crypto (Crypto)
Expand Down Expand Up @@ -112,7 +112,7 @@ newtype ConwayGovCertEvent era = GovCertEvent (Event (EraRule "GOVCERT" era))
instance
( EraPParams era
, State (EraRule "GOVCERT" era) ~ VState era
, Signal (EraRule "GOVCERT" era) ~ ConwayCommitteeCert (EraCrypto era)
, Signal (EraRule "GOVCERT" era) ~ ConwayGovCert (EraCrypto era)
, Environment (EraRule "GOVCERT" era) ~ PParams era
, EraRule "GOVCERT" era ~ ConwayGOVCERT era
, Eq (PredicateFailure (EraRule "GOVCERT" era))
Expand All @@ -121,7 +121,7 @@ instance
STS (ConwayGOVCERT era)
where
type State (ConwayGOVCERT era) = VState era
type Signal (ConwayGOVCERT era) = ConwayCommitteeCert (EraCrypto era)
type Signal (ConwayGOVCERT era) = ConwayGovCert (EraCrypto era)
type Environment (ConwayGOVCERT era) = PParams era
type BaseM (ConwayGOVCERT era) = ShelleyBase
type PredicateFailure (ConwayGOVCERT era) = ConwayGovCertPredFailure era
Expand Down
55 changes: 30 additions & 25 deletions eras/conway/impl/src/Cardano/Ledger/Conway/TxCert.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@
module Cardano.Ledger.Conway.TxCert (
ConwayTxCert (..),
ConwayDelegCert (..),
ConwayCommitteeCert (..),
ConwayGovCert (..),
Delegatee (..),
ConwayEraTxCert (..),
fromShelleyDelegCert,
Expand Down Expand Up @@ -172,22 +172,22 @@ instance Crypto c => ConwayEraTxCert (ConwayEra c) where
getRegDepositDelegTxCert (ConwayTxCertDeleg (ConwayRegDelegCert cred d c)) = Just (cred, d, c)
getRegDepositDelegTxCert _ = Nothing

mkAuthCommitteeHotKeyTxCert ck hk = ConwayTxCertCommittee $ ConwayAuthCommitteeHotKey ck hk
getAuthCommitteeHotKeyTxCert (ConwayTxCertCommittee (ConwayAuthCommitteeHotKey ck hk)) = Just (ck, hk)
mkAuthCommitteeHotKeyTxCert ck hk = ConwayTxCertGov $ ConwayAuthCommitteeHotKey ck hk
getAuthCommitteeHotKeyTxCert (ConwayTxCertGov (ConwayAuthCommitteeHotKey ck hk)) = Just (ck, hk)
getAuthCommitteeHotKeyTxCert _ = Nothing

mkResignCommitteeColdTxCert = ConwayTxCertCommittee . ConwayResignCommitteeColdKey
getResignCommitteeColdTxCert (ConwayTxCertCommittee (ConwayResignCommitteeColdKey ck)) = Just ck
mkResignCommitteeColdTxCert = ConwayTxCertGov . ConwayResignCommitteeColdKey
getResignCommitteeColdTxCert (ConwayTxCertGov (ConwayResignCommitteeColdKey ck)) = Just ck
getResignCommitteeColdTxCert _ = Nothing

mkRegDRepTxCert cred deposit mAnchor = ConwayTxCertCommittee $ ConwayRegDRep cred deposit mAnchor
mkRegDRepTxCert cred deposit mAnchor = ConwayTxCertGov $ ConwayRegDRep cred deposit mAnchor
getRegDRepTxCert = \case
ConwayTxCertCommittee (ConwayRegDRep cred deposit mAnchor) -> Just (cred, deposit, mAnchor)
ConwayTxCertGov (ConwayRegDRep cred deposit mAnchor) -> Just (cred, deposit, mAnchor)
_ -> Nothing

mkUnRegDRepTxCert cred deposit = ConwayTxCertCommittee $ ConwayUnRegDRep cred deposit
mkUnRegDRepTxCert cred deposit = ConwayTxCertGov $ ConwayUnRegDRep cred deposit
getUnRegDRepTxCert = \case
ConwayTxCertCommittee (ConwayUnRegDRep cred deposit) -> Just (cred, deposit)
ConwayTxCertGov (ConwayUnRegDRep cred deposit) -> Just (cred, deposit)
_ -> Nothing

pattern RegDepositTxCert ::
Expand Down Expand Up @@ -320,21 +320,21 @@ instance NFData (ConwayDelegCert c)

instance NoThunks (ConwayDelegCert c)

data ConwayCommitteeCert c
data ConwayGovCert c
= ConwayRegDRep !(Credential 'Voting c) !Coin !(StrictMaybe (Anchor c))
| ConwayUnRegDRep !(Credential 'Voting c) !Coin
| ConwayAuthCommitteeHotKey !(Credential 'CommitteeColdKey c) !(Credential 'CommitteeHotKey c)
| ConwayResignCommitteeColdKey !(Credential 'CommitteeColdKey c)
deriving (Show, Generic, Eq)

instance Crypto c => NFData (ConwayCommitteeCert c)
instance Crypto c => NFData (ConwayGovCert c)

instance NoThunks (ConwayCommitteeCert c)
instance NoThunks (ConwayGovCert c)

data ConwayTxCert era
= ConwayTxCertDeleg !(ConwayDelegCert (EraCrypto era))
| ConwayTxCertPool !(PoolCert (EraCrypto era))
| ConwayTxCertCommittee !(ConwayCommitteeCert (EraCrypto era))
| ConwayTxCertGov !(ConwayGovCert (EraCrypto era))
deriving (Show, Generic, Eq)

instance Crypto (EraCrypto era) => NFData (ConwayTxCert era)
Expand Down Expand Up @@ -417,7 +417,7 @@ instance (Era era, Val (Value era)) => EncCBOR (ConwayTxCert era) where
encCBOR = \case
ConwayTxCertDeleg delegCert -> encodeConwayDelegCert delegCert
ConwayTxCertPool poolCert -> encodePoolCert poolCert
ConwayTxCertCommittee committeeCert -> encodeCommitteeHotKey committeeCert
ConwayTxCertGov committeeCert -> encodeCommitteeHotKey committeeCert

encodeConwayDelegCert :: Crypto c => ConwayDelegCert c -> Encoding
encodeConwayDelegCert = \case
Expand Down Expand Up @@ -467,7 +467,7 @@ encodeConwayDelegCert = \case
<> encCBOR dRep
<> encCBOR deposit

encodeCommitteeHotKey :: Crypto c => ConwayCommitteeCert c -> Encoding
encodeCommitteeHotKey :: Crypto c => ConwayGovCert c -> Encoding
encodeCommitteeHotKey = \case
ConwayAuthCommitteeHotKey cred key ->
encodeListLen 3
Expand All @@ -483,7 +483,7 @@ encodeCommitteeHotKey = \case
<> encodeWord8 16
<> encCBOR cred
<> encCBOR deposit
<> (encodeNullStrictMaybe encCBOR) mAnchor
<> encodeNullStrictMaybe encCBOR mAnchor
ConwayUnRegDRep cred deposit ->
encodeListLen 3
<> encodeWord8 17
Expand Down Expand Up @@ -520,14 +520,17 @@ getScriptWitnessConwayTxCert = \case
ConwayUnRegCert cred _ -> credScriptHash cred
ConwayDelegCert cred _ -> credScriptHash cred
ConwayRegDelegCert cred _ _ -> credScriptHash cred
ConwayTxCertCommittee committeeCert -> committeeWitness committeeCert
_ -> Nothing
-- PoolIds can't be Scripts
ConwayTxCertPool {} -> Nothing
ConwayTxCertGov govCert -> govWitness govCert
where
committeeWitness :: ConwayCommitteeCert c -> Maybe (ScriptHash c)
committeeWitness = \case
govWitness :: ConwayGovCert c -> Maybe (ScriptHash c)
govWitness = \case
ConwayAuthCommitteeHotKey coldCred _hotCred -> credScriptHash coldCred
ConwayResignCommitteeColdKey coldCred -> credScriptHash coldCred
_ -> Nothing
-- Registration of a DRep does not require a witness
ConwayRegDRep {} -> Nothing
ConwayUnRegDRep cred _ -> credScriptHash cred

getVKeyWitnessConwayTxCert :: ConwayTxCert era -> Maybe (KeyHash 'Witness (EraCrypto era))
getVKeyWitnessConwayTxCert = \case
Expand All @@ -539,10 +542,12 @@ getVKeyWitnessConwayTxCert = \case
ConwayDelegCert cred _ -> credKeyHashWitness cred
ConwayRegDelegCert cred _ _ -> credKeyHashWitness cred
ConwayTxCertPool poolCert -> Just $ poolCertKeyHashWitness poolCert
ConwayTxCertCommittee committeeCert -> committeeWitness committeeCert
ConwayTxCertGov govCert -> govWitness govCert
where
committeeWitness :: ConwayCommitteeCert c -> Maybe (KeyHash 'Witness c)
committeeWitness = \case
govWitness :: ConwayGovCert c -> Maybe (KeyHash 'Witness c)
govWitness = \case
ConwayAuthCommitteeHotKey coldCred _hotCred -> credKeyHashWitness coldCred
ConwayResignCommitteeColdKey coldCred -> credKeyHashWitness coldCred
_ -> Nothing
-- Registration of a DRep does not require a witness
ConwayRegDRep {} -> Nothing
ConwayUnRegDRep cred _ -> credKeyHashWitness cred
Original file line number Diff line number Diff line change
Expand Up @@ -69,10 +69,10 @@ instance Era era => Arbitrary (ConwayTxCert era) where
oneof
[ ConwayTxCertDeleg <$> arbitrary
, ConwayTxCertPool <$> arbitrary
, ConwayTxCertCommittee <$> arbitrary
, ConwayTxCertGov <$> arbitrary
]

instance Crypto c => Arbitrary (ConwayCommitteeCert c) where
instance Crypto c => Arbitrary (ConwayGovCert c) where
arbitrary =
oneof
[ ConwayRegDRep <$> arbitrary <*> arbitrary <*> arbitrary
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,8 @@ import Cardano.Ledger.Conway.Rules (
)
import Cardano.Ledger.Conway.TxBody (ConwayTxBody (..))
import Cardano.Ledger.Conway.TxCert (
ConwayCommitteeCert (..),
ConwayDelegCert (..),
ConwayGovCert (..),
ConwayTxCert (..),
Delegatee (..),
)
Expand Down Expand Up @@ -135,10 +135,10 @@ ppConwayTxCert :: ConwayTxCert era -> PDoc
ppConwayTxCert = \case
ConwayTxCertDeleg dc -> ppSexp "ConwayTxCertDeleg" [prettyA dc]
ConwayTxCertPool pc -> ppSexp "ConwayTxCertPool" [ppPoolCert pc]
ConwayTxCertCommittee gdc -> ppSexp "ConwayTxCertCommittee" [ppConwayCommitteeCert gdc]
ConwayTxCertGov gdc -> ppSexp "ConwayTxCertGov" [ppConwayGovCert gdc]

ppConwayCommitteeCert :: ConwayCommitteeCert c -> PDoc
ppConwayCommitteeCert = \case
ppConwayGovCert :: ConwayGovCert c -> PDoc
ppConwayGovCert = \case
ConwayRegDRep cred deposit mAnchor ->
ppSexp "ConwayRegDRep" [prettyA cred, prettyA deposit, prettyA mAnchor]
ConwayUnRegDRep cred deposit ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1463,7 +1463,7 @@ pcShelleyTxCert (ShelleyTxCertMir _) = ppString "MirCert"
pcConwayTxCert :: ConwayTxCert c -> PDoc
pcConwayTxCert (ConwayTxCertDeleg dc) = prettyA dc
pcConwayTxCert (ConwayTxCertPool poolc) = pcPoolCert poolc
pcConwayTxCert (ConwayTxCertCommittee _) = ppString "ConwayTxCertCommittee" -- TODO: @aniketd add pretty instance for the certs
pcConwayTxCert (ConwayTxCertGov _) = ppString "ConwayTxCertGov" -- TODO: @aniketd add pretty instance for the certs

instance c ~ EraCrypto era => PrettyC (ShelleyTxCert c) era where prettyC _ = pcShelleyTxCert

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -828,7 +828,7 @@ getConwayTxCertCredential (ConwayTxCertDeleg (ConwayRegCert _ _)) = Nothing
getConwayTxCertCredential (ConwayTxCertDeleg (ConwayUnRegCert cred _)) = Just cred
getConwayTxCertCredential (ConwayTxCertDeleg (ConwayDelegCert cred _)) = Just cred
getConwayTxCertCredential (ConwayTxCertDeleg (ConwayRegDelegCert cred _ _)) = Just cred
getConwayTxCertCredential (ConwayTxCertCommittee _) = Nothing
getConwayTxCertCredential (ConwayTxCertGov _) = Nothing

genWithdrawals :: Reflect era => SlotNo -> GenRS era (Withdrawals (EraCrypto era), RewardAccounts (EraCrypto era))
genWithdrawals slot =
Expand Down

0 comments on commit 454a7d3

Please sign in to comment.