Skip to content

Commit

Permalink
Add PParams for Conway
Browse files Browse the repository at this point in the history
  • Loading branch information
aniketd authored and Soupstraw committed Jul 20, 2023
1 parent a86a2c6 commit 7b20016
Show file tree
Hide file tree
Showing 12 changed files with 929 additions and 70 deletions.
4 changes: 2 additions & 2 deletions eras/babbage/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
# Version history for `cardano-ledger-babbage`

## 1.4.0.1
## 1.4.1.0

*
* Added `babbagePParamsHKDPairs`

## 1.4.0.0

Expand Down
2 changes: 1 addition & 1 deletion eras/babbage/impl/cardano-ledger-babbage.cabal
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
cabal-version: 3.0
name: cardano-ledger-babbage
version: 1.4.0.2
version: 1.4.1.0
license: Apache-2.0
maintainer: operations@iohk.io
author: IOHK
Expand Down
2 changes: 1 addition & 1 deletion eras/babbage/impl/src/Cardano/Ledger/Babbage/PParams.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ module Cardano.Ledger.Babbage.PParams (
encodeLangViews,
coinsPerUTxOWordToCoinsPerUTxOByte,
coinsPerUTxOByteToCoinsPerUTxOWord,
babbagePParamsHKDPairs,
)
where

Expand Down Expand Up @@ -233,7 +234,6 @@ instance Crypto c => BabbageEraPParams (BabbageEra c) where
instance Crypto c => EraGovernance (BabbageEra c) where
type GovernanceState (BabbageEra c) = ShelleyPPUPState (BabbageEra c)
emptyGovernanceState = ShelleyPPUPState emptyPPPUpdates emptyPPPUpdates

getProposedPPUpdates = Just . proposals

instance Era era => EncCBOR (BabbagePParams Identity era) where
Expand Down
5 changes: 5 additions & 0 deletions eras/conway/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,11 @@
## 1.6.0.0

* Removal of `GovernanceProcedure` in favor of `GovernanceProcedures`
* Add `ConwayPParams` #3498
* Add `UpgradeConwayPParams` #3498
* Add `ConwayEraPParams` #3498
* Add `PoolVotingThresholds` #3498
* Add `DRepVotingThresholds` #3498

## 1.5.0.0

Expand Down
2 changes: 1 addition & 1 deletion eras/conway/impl/cardano-ledger-conway.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ library
cardano-ledger-binary >=1.1,
cardano-ledger-allegra >=1.1,
cardano-ledger-alonzo ^>=1.4,
cardano-ledger-babbage >=1.1,
cardano-ledger-babbage >=1.4.1,
cardano-ledger-core >=1.4 && <1.6,
cardano-ledger-mary >=1.1,
cardano-ledger-shelley ^>=1.4.1,
Expand Down
165 changes: 165 additions & 0 deletions eras/conway/impl/src/Cardano/Ledger/Conway/Core.hs
Original file line number Diff line number Diff line change
@@ -1,21 +1,186 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}

module Cardano.Ledger.Conway.Core (
module X,
ConwayEraTxBody (..),
ConwayEraPParams (..),
ppPoolVotingThresholdsL,
ppDRepVotingThresholdsL,
ppMinCommitteeSizeL,
ppCommitteeTermLimitL,
ppGovActionExpirationL,
ppGovActionDepositL,
ppDRepDepositL,
ppDRepActivityL,
ppuPoolVotingThresholdsL,
ppuDRepVotingThresholdsL,
ppuMinCommitteeSizeL,
ppuCommitteeTermLimitL,
ppuGovActionExpirationL,
ppuGovActionDepositL,
ppuDRepDepositL,
ppuDRepActivityL,
PoolVotingThresholds (..),
DRepVotingThresholds (..),
)
where

import Cardano.Ledger.Babbage.Core as X
import Cardano.Ledger.BaseTypes (EpochNo, StrictMaybe, UnitInterval)
import Cardano.Ledger.Binary (DecCBOR, EncCBOR, decodeRecordNamed, encodeListLen)
import Cardano.Ledger.Binary.Decoding (DecCBOR (decCBOR))
import Cardano.Ledger.Binary.Encoding (EncCBOR (encCBOR))
import Cardano.Ledger.Coin (Coin)
import Cardano.Ledger.Conway.Governance (ProposalProcedure, VotingProcedure)
import Cardano.Ledger.HKD (HKD, HKDFunctor)
import Control.DeepSeq (NFData)
import Data.Aeson (ToJSON)
import Data.Default.Class (Default)
import Data.Functor.Identity (Identity)
import Data.Sequence.Strict (StrictSeq)
import GHC.Generics (Generic)
import Lens.Micro (Lens')
import NoThunks.Class (NoThunks)
import Numeric.Natural (Natural)

class BabbageEraTxBody era => ConwayEraTxBody era where
votingProceduresTxBodyL :: Lens' (TxBody era) (StrictSeq (VotingProcedure era))
proposalProceduresTxBodyL :: Lens' (TxBody era) (StrictSeq (ProposalProcedure era))

class BabbageEraPParams era => ConwayEraPParams era where
hkdPoolVotingThresholdsL :: HKDFunctor f => Lens' (PParamsHKD f era) (HKD f PoolVotingThresholds)
hkdDRepVotingThresholdsL :: HKDFunctor f => Lens' (PParamsHKD f era) (HKD f DRepVotingThresholds)
hkdMinCommitteeSizeL :: HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Natural)
hkdCommitteeTermLimitL :: HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Natural)
hkdGovActionExpirationL :: HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Natural)
hkdGovActionDepositL :: HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin)
hkdDRepDepositL :: HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin)
hkdDRepActivityL :: HKDFunctor f => Lens' (PParamsHKD f era) (HKD f EpochNo)

ppPoolVotingThresholdsL :: forall era. ConwayEraPParams era => Lens' (PParams era) PoolVotingThresholds
ppPoolVotingThresholdsL = ppLens . hkdPoolVotingThresholdsL @era @Identity

ppDRepVotingThresholdsL :: forall era. ConwayEraPParams era => Lens' (PParams era) DRepVotingThresholds
ppDRepVotingThresholdsL = ppLens . hkdDRepVotingThresholdsL @era @Identity

ppMinCommitteeSizeL :: forall era. ConwayEraPParams era => Lens' (PParams era) Natural
ppMinCommitteeSizeL = ppLens . hkdMinCommitteeSizeL @era @Identity

ppCommitteeTermLimitL :: forall era. ConwayEraPParams era => Lens' (PParams era) Natural
ppCommitteeTermLimitL = ppLens . hkdCommitteeTermLimitL @era @Identity

ppGovActionExpirationL :: forall era. ConwayEraPParams era => Lens' (PParams era) Natural
ppGovActionExpirationL = ppLens . hkdGovActionExpirationL @era @Identity

ppGovActionDepositL :: forall era. ConwayEraPParams era => Lens' (PParams era) Coin
ppGovActionDepositL = ppLens . hkdGovActionDepositL @era @Identity

ppDRepDepositL :: forall era. ConwayEraPParams era => Lens' (PParams era) Coin
ppDRepDepositL = ppLens . hkdDRepDepositL @era @Identity

ppDRepActivityL :: forall era. ConwayEraPParams era => Lens' (PParams era) EpochNo
ppDRepActivityL = ppLens . hkdDRepActivityL @era @Identity

ppuPoolVotingThresholdsL :: forall era. ConwayEraPParams era => Lens' (PParamsUpdate era) (StrictMaybe PoolVotingThresholds)
ppuPoolVotingThresholdsL = ppuLens . hkdPoolVotingThresholdsL @era @StrictMaybe

ppuDRepVotingThresholdsL :: forall era. ConwayEraPParams era => Lens' (PParamsUpdate era) (StrictMaybe DRepVotingThresholds)
ppuDRepVotingThresholdsL = ppuLens . hkdDRepVotingThresholdsL @era @StrictMaybe

ppuMinCommitteeSizeL :: forall era. ConwayEraPParams era => Lens' (PParamsUpdate era) (StrictMaybe Natural)
ppuMinCommitteeSizeL = ppuLens . hkdMinCommitteeSizeL @era @StrictMaybe

ppuCommitteeTermLimitL :: forall era. ConwayEraPParams era => Lens' (PParamsUpdate era) (StrictMaybe Natural)
ppuCommitteeTermLimitL = ppuLens . hkdCommitteeTermLimitL @era @StrictMaybe

ppuGovActionExpirationL :: forall era. ConwayEraPParams era => Lens' (PParamsUpdate era) (StrictMaybe Natural)
ppuGovActionExpirationL = ppuLens . hkdGovActionExpirationL @era @StrictMaybe

ppuGovActionDepositL :: forall era. ConwayEraPParams era => Lens' (PParamsUpdate era) (StrictMaybe Coin)
ppuGovActionDepositL = ppuLens . hkdGovActionDepositL @era @StrictMaybe

ppuDRepDepositL :: forall era. ConwayEraPParams era => Lens' (PParamsUpdate era) (StrictMaybe Coin)
ppuDRepDepositL = ppuLens . hkdDRepDepositL @era @StrictMaybe

ppuDRepActivityL :: forall era. ConwayEraPParams era => Lens' (PParamsUpdate era) (StrictMaybe EpochNo)
ppuDRepActivityL = ppuLens . hkdDRepActivityL @era @StrictMaybe

data PoolVotingThresholds = PoolVotingThresholds
{ pvtMotionNoConfidence :: !UnitInterval
, pvtCommitteeNormal :: !UnitInterval
, pvtCommitteeNoConfidence :: !UnitInterval
, pvtHardForkInitiation :: !UnitInterval
}
deriving (Eq, Ord, Show, Generic, Default, ToJSON, NFData, NoThunks)

instance EncCBOR PoolVotingThresholds where
encCBOR PoolVotingThresholds {..} =
encodeListLen 4
<> encCBOR pvtMotionNoConfidence
<> encCBOR pvtCommitteeNormal
<> encCBOR pvtCommitteeNoConfidence
<> encCBOR pvtHardForkInitiation

instance DecCBOR PoolVotingThresholds where
decCBOR =
decodeRecordNamed "PoolVotingThresholds" (const 4) $ do
pvtMotionNoConfidence <- decCBOR
pvtCommitteeNormal <- decCBOR
pvtCommitteeNoConfidence <- decCBOR
pvtHardForkInitiation <- decCBOR
pure $ PoolVotingThresholds {..}

data DRepVotingThresholds = DRepVotingThresholds
{ dvtMotionNoConfidence :: !UnitInterval
, dvtCommitteeNormal :: !UnitInterval
, dvtCommitteeNoConfidence :: !UnitInterval
, dvtUpdateToConstitution :: !UnitInterval
, dvtHardForkInitiation :: !UnitInterval
, dvtPPNetworkGroup :: !UnitInterval
, dvtPPEconomicGroup :: !UnitInterval
, dvtPPTechnicalGroup :: !UnitInterval
, dvtPPGovernanceGroup :: !UnitInterval
, dvtTreasuryWithdrawal :: !UnitInterval
}
deriving (Eq, Ord, Show, Generic, Default, ToJSON, NFData, NoThunks)

instance EncCBOR DRepVotingThresholds where
encCBOR DRepVotingThresholds {..} =
encodeListLen 10
<> encCBOR dvtMotionNoConfidence
<> encCBOR dvtCommitteeNormal
<> encCBOR dvtCommitteeNoConfidence
<> encCBOR dvtUpdateToConstitution
<> encCBOR dvtHardForkInitiation
<> encCBOR dvtPPNetworkGroup
<> encCBOR dvtPPEconomicGroup
<> encCBOR dvtPPTechnicalGroup
<> encCBOR dvtPPGovernanceGroup
<> encCBOR dvtTreasuryWithdrawal

instance DecCBOR DRepVotingThresholds where
decCBOR =
decodeRecordNamed "DRepVotingThresholds" (const 10) $ do
dvtMotionNoConfidence <- decCBOR
dvtCommitteeNormal <- decCBOR
dvtCommitteeNoConfidence <- decCBOR
dvtUpdateToConstitution <- decCBOR
dvtHardForkInitiation <- decCBOR
dvtPPNetworkGroup <- decCBOR
dvtPPEconomicGroup <- decCBOR
dvtPPTechnicalGroup <- decCBOR
dvtPPGovernanceGroup <- decCBOR
dvtTreasuryWithdrawal <- decCBOR
pure $ DRepVotingThresholds {..}
4 changes: 1 addition & 3 deletions eras/conway/impl/src/Cardano/Ledger/Conway/Governance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,10 +70,8 @@ import Cardano.Ledger.Conway.Governance.Procedures (
VotingProcedure (..),
govActionIdToText,
)
import Cardano.Ledger.Conway.PParams ()
import Cardano.Ledger.Core
import Cardano.Ledger.Credential (Credential (..))
import Cardano.Ledger.Crypto (Crypto)
import Cardano.Ledger.Keys (KeyHash (..), KeyRole (..))
import Cardano.Ledger.SafeHash (SafeHash)
import Cardano.Ledger.Shelley.Governance
Expand Down Expand Up @@ -344,6 +342,6 @@ toConwayGovernancePairs cg@(ConwayGovernance _ _) =
, "ratify" .= cgRatify
]

instance Crypto c => EraGovernance (ConwayEra c) where
instance EraPParams (ConwayEra c) => EraGovernance (ConwayEra c) where
type GovernanceState (ConwayEra c) = ConwayGovernance (ConwayEra c)
getConstitutionHash g = Just $ g ^. cgRatifyL . rsEnactStateL . ensConstitutionL
Loading

0 comments on commit 7b20016

Please sign in to comment.