Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions eras/allegra/impl/src/Cardano/Ledger/Allegra/PParams.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,8 @@ instance EraPParams AllegraEra where
upgradePParamsHKD () = coerce
downgradePParamsHKD () = coerce

hkdMinFeeACompactL = lens sppMinFeeA $ \pp x -> pp {sppMinFeeA = x}
hkdMinFeeBCompactL = lens sppMinFeeB $ \pp x -> pp {sppMinFeeB = x}
hkdMinFeeFactorL = lens sppMinFeeFactor $ \pp x -> pp {sppMinFeeFactor = x}
hkdMinFeeConstantCompactL = lens sppMinFeeConstant $ \pp x -> pp {sppMinFeeConstant = x}
hkdMaxBBSizeL = lens sppMaxBBSize $ \pp x -> pp {sppMaxBBSize = x}
hkdMaxTxSizeL = lens sppMaxTxSize $ \pp x -> pp {sppMaxTxSize = x}
hkdMaxBHSizeL = lens sppMaxBHSize $ \pp x -> pp {sppMaxBHSize = x}
Expand Down
5 changes: 4 additions & 1 deletion eras/alonzo/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,12 @@

## 1.15.0.0

* Renamed:
- `appMinFeeA` -> `appMinFeeFactor`
- `appMinFeeB` -> `appMinFeeConstant`
* Changed type of `appMinFeeA` to `CoinPerByte`
* Changed the type of `dappMinUTxOValue` to `CompactForm Coin` in `DowngradeAlonzoPParams`
* Changed the type of the following fields to `CompactForm Coin` in `AlonzoPParams`:
- `appMinFeeA`
- `appMinFeeB`
- `appKeyDeposit`
- `appMinPoolCost`
Expand Down
40 changes: 26 additions & 14 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/PParams.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,6 +64,10 @@ module Cardano.Ledger.Alonzo.PParams (
ppMaxTxExUnits,
ppMaxValSize,
ppPrices,

-- * Deprecated
appMinFeeA,
appMinFeeB,
) where

import Cardano.Ledger.Alonzo.Era (AlonzoEra)
Expand Down Expand Up @@ -223,9 +227,9 @@ ppuMaxCollateralInputsL = ppuLensHKD . hkdMaxCollateralInputsL @era @StrictMaybe
-- | Protocol parameters.
-- Shelley parameters + additional ones
data AlonzoPParams f era = AlonzoPParams
{ appMinFeeA :: !(HKD f (CompactForm Coin))
{ appMinFeeFactor :: !(HKD f CoinPerByte)
-- ^ The linear factor for the minimum fee calculation
, appMinFeeB :: !(HKD f (CompactForm Coin))
, appMinFeeConstant :: !(HKD f (CompactForm Coin))
-- ^ The constant factor for the minimum fee calculation
, appMaxBBSize :: !(HKD f Word32)
-- ^ Maximal block body size
Expand Down Expand Up @@ -280,6 +284,14 @@ data AlonzoPParams f era = AlonzoPParams
}
deriving (Generic)

appMinFeeA :: AlonzoPParams f era -> HKD f CoinPerByte
appMinFeeA = appMinFeeFactor
{-# DEPRECATED appMinFeeA "In favor of `appMinFeeFactor`" #-}

appMinFeeB :: AlonzoPParams f era -> HKD f (CompactForm Coin)
appMinFeeB = appMinFeeConstant
{-# DEPRECATED appMinFeeB "In favor of `appMinFeeConstant`" #-}

deriving instance Eq (AlonzoPParams Identity era)

deriving instance Ord (AlonzoPParams Identity era)
Expand Down Expand Up @@ -312,8 +324,8 @@ instance EraPParams AlonzoEra where
downgradePParamsHKD = downgradeAlonzoPParams
emptyUpgradePParamsUpdate = emptyAlonzoUpgradePParamsUpdate

hkdMinFeeACompactL = lens appMinFeeA $ \pp x -> pp {appMinFeeA = x}
hkdMinFeeBCompactL = lens appMinFeeB $ \pp x -> pp {appMinFeeB = x}
hkdMinFeeFactorL = lens appMinFeeFactor $ \pp x -> pp {appMinFeeFactor = x}
hkdMinFeeConstantCompactL = lens appMinFeeConstant $ \pp x -> pp {appMinFeeConstant = x}
hkdMaxBBSizeL = lens appMaxBBSize $ \pp x -> pp {appMaxBBSize = x}
hkdMaxTxSizeL = lens appMaxTxSize $ \pp x -> pp {appMaxTxSize = x}
hkdMaxBHSizeL = lens appMaxBHSize $ \pp x -> pp {appMaxBHSize = x}
Expand All @@ -331,8 +343,8 @@ instance EraPParams AlonzoEra where
hkdMinPoolCostCompactL = lens appMinPoolCost $ \pp x -> pp {appMinPoolCost = x}

eraPParams =
[ ppMinFeeA
, ppMinFeeB
[ ppMinFeeFactor
, ppMinFeeConstant
, ppMaxBBSize
, ppMaxTxSize
, ppMaxBHSize
Expand Down Expand Up @@ -470,8 +482,8 @@ instance NFData (DowngradeAlonzoPParams Identity)
emptyAlonzoPParams :: forall era. Era era => AlonzoPParams Identity era
emptyAlonzoPParams =
AlonzoPParams
{ appMinFeeA = CompactCoin 0
, appMinFeeB = CompactCoin 0
{ appMinFeeFactor = CoinPerByte $ Coin 0
, appMinFeeConstant = CompactCoin 0
, appMaxBBSize = 0
, appMaxTxSize = 2048
, appMaxBHSize = 0
Expand Down Expand Up @@ -500,8 +512,8 @@ emptyAlonzoPParams =
emptyAlonzoPParamsUpdate :: AlonzoPParams StrictMaybe era
emptyAlonzoPParamsUpdate =
AlonzoPParams
{ appMinFeeA = SNothing
, appMinFeeB = SNothing
{ appMinFeeFactor = SNothing
, appMinFeeConstant = SNothing
, appMaxBBSize = SNothing
, appMaxTxSize = SNothing
, appMaxBHSize = SNothing
Expand Down Expand Up @@ -594,8 +606,8 @@ upgradeAlonzoPParams ::
AlonzoPParams f era2
upgradeAlonzoPParams UpgradeAlonzoPParams {..} ShelleyPParams {..} =
AlonzoPParams
{ appMinFeeA = sppMinFeeA
, appMinFeeB = sppMinFeeB
{ appMinFeeFactor = sppMinFeeFactor
, appMinFeeConstant = sppMinFeeConstant
, appMaxBBSize = sppMaxBBSize
, appMaxTxSize = sppMaxTxSize
, appMaxBHSize = sppMaxBHSize
Expand Down Expand Up @@ -625,8 +637,8 @@ upgradeAlonzoPParams UpgradeAlonzoPParams {..} ShelleyPParams {..} =
downgradeAlonzoPParams :: DowngradeAlonzoPParams f -> AlonzoPParams f era2 -> ShelleyPParams f era1
downgradeAlonzoPParams DowngradeAlonzoPParams {dappMinUTxOValue} AlonzoPParams {..} =
ShelleyPParams
{ sppMinFeeA = appMinFeeA
, sppMinFeeB = appMinFeeB
{ sppMinFeeFactor = appMinFeeFactor
, sppMinFeeConstant = appMinFeeConstant
, sppMaxBBSize = appMaxBBSize
, sppMaxTxSize = appMaxTxSize
, sppMaxBHSize = appMaxBHSize
Expand Down
4 changes: 2 additions & 2 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -369,8 +369,8 @@ alonzoMinFeeTx ::
Tx l era ->
Coin
alonzoMinFeeTx pp tx =
(tx ^. sizeTxF <×> pp ^. ppMinFeeAL)
<+> (pp ^. ppMinFeeBL)
(tx ^. sizeTxF <×> unCoinPerByte (pp ^. ppMinFeeFactorL))
<+> (pp ^. ppMinFeeConstantL)
<+> txscriptfee (pp ^. ppPricesL) allExunits
where
allExunits = totExUnits tx
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -548,7 +548,7 @@ sumCollateral tx utxo =
sumCoinUTxO $ txInsFilter utxo $ tx ^. bodyTxL . collateralInputsTxBodyL

storageCost :: forall era t. (EraPParams era, EncCBOR t) => Integer -> PParams era -> t -> Coin
storageCost extra pp x = (extra + encodedLen @era x) <×> pp ^. ppMinFeeAL
storageCost extra pp x = (extra + encodedLen @era x) <×> unCoinPerByte (pp ^. ppMinFeeFactorL)

addRedeemMap ::
(P.Data, Natural, Natural) ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -298,8 +298,8 @@ goldenMinFee =
pricesParam = Prices priceMem priceSteps
pp =
emptyPParams
& ppMinFeeAL .~ Coin 44
& ppMinFeeBL .~ Coin 155381
& ppMinFeeFactorL .~ CoinPerByte (Coin 44)
& ppMinFeeConstantL .~ Coin 155381
& ppPricesL .~ pricesParam

Coin 1006053 `shouldBe` alonzoMinFeeTx pp firstTx
Expand Down
7 changes: 6 additions & 1 deletion eras/babbage/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,14 @@

## 1.13.0.0

* Renamed:
- `bppMinFeeA` -> `bppMinFeeFactor`
- `bppMinFeeB` -> `bppMinFeeConstant`
* Changed type of `bppMinFeeA` to `CoinPerByte`
* Moved `CoinPerByte` to `cardano-ledger-core`
* Add `babbageUtxoValidation`
* Add `babbageUtxoTests`
* Changed the type of the following fields to `CompactForm Coin` in `BabbagePParams`:
- `bppMinFeeA`
- `bppMinFeeB`
- `bppKeyDeposit`
- `bppMinPoolCost`
Expand Down Expand Up @@ -40,6 +44,7 @@

### `testlib`

* Moved `Arbitrary` and `ToExpr` instances of `CoinPerByte` to `cardano-ledger-core`
* Add `plutus_v2_script` to CDDL exports
* Hide Shelley CDDL `protocol_version` and re-export a new one for Babbage
* Use fixed-sized `uint .size 8` for `slot` and `block_number` in CDDL for header
Expand Down
1 change: 0 additions & 1 deletion eras/babbage/impl/src/Cardano/Ledger/Babbage/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@ module Cardano.Ledger.Babbage.Core (
import Cardano.Ledger.Alonzo.Core
import Cardano.Ledger.Babbage.PParams (
BabbageEraPParams (..),
CoinPerByte (..),
ppCoinsPerUTxOByteL,
ppuCoinsPerUTxOByteL,
)
Expand Down
58 changes: 26 additions & 32 deletions eras/babbage/impl/src/Cardano/Ledger/Babbage/PParams.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,6 @@
-- | This module contains the type of protocol parameters and EraPParams instance
module Cardano.Ledger.Babbage.PParams (
BabbageEraPParams (..),
CoinPerByte (..),
ppCoinsPerUTxOByteL,
ppuCoinsPerUTxOByteL,
BabbagePParams (..),
Expand All @@ -36,6 +35,10 @@ module Cardano.Ledger.Babbage.PParams (
coinsPerUTxOWordToCoinsPerUTxOByte,
coinsPerUTxOByteToCoinsPerUTxOWord,
ppCoinsPerUTxOByte,

-- * Deprecated
bppMinFeeA,
bppMinFeeB,
) where

import Cardano.Ledger.Alonzo (AlonzoEra)
Expand All @@ -56,21 +59,12 @@ import Cardano.Ledger.BaseTypes (
StrictMaybe (..),
UnitInterval,
)
import Cardano.Ledger.Binary (
DecCBOR (..),
EncCBOR (..),
)
import Cardano.Ledger.Coin (Coin (..), CompactForm (..))
import Cardano.Ledger.Core (EraPParams (..))
import Cardano.Ledger.HKD (HKDFunctor (..))
import Cardano.Ledger.Orphans ()
import Cardano.Ledger.Plutus.ToPlutusData (ToPlutusData (..))
import Cardano.Ledger.Shelley.PParams
import Control.DeepSeq (NFData)
import Data.Aeson as Aeson (
FromJSON (..),
ToJSON (..),
)
import Data.Functor.Identity (Identity (..))
import Data.Proxy (Proxy (Proxy))
import Data.Word (Word16, Word32)
Expand All @@ -79,14 +73,6 @@ import Lens.Micro
import NoThunks.Class (NoThunks (..))
import Numeric.Natural (Natural)

newtype CoinPerByte = CoinPerByte {unCoinPerByte :: Coin}
deriving stock (Eq, Ord)
deriving newtype (EncCBOR, DecCBOR, ToJSON, FromJSON, NFData, NoThunks, Show)

instance ToPlutusData CoinPerByte where
toPlutusData (CoinPerByte c) = toPlutusData @Coin c
fromPlutusData x = CoinPerByte <$> fromPlutusData @Coin x

class AlonzoEraPParams era => BabbageEraPParams era where
hkdCoinsPerUTxOByteL :: HKDFunctor f => Lens' (PParamsHKD f era) (HKD f CoinPerByte)

Expand All @@ -101,9 +87,9 @@ ppuCoinsPerUTxOByteL = ppuLensHKD . hkdCoinsPerUTxOByteL @era @StrictMaybe
-- | Babbage Protocol parameters. Ways in which parameters have changed from Alonzo: lack
-- of @d@, @extraEntropy@ and replacement of @coinsPerUTxOWord@ with @coinsPerUTxOByte@
data BabbagePParams f era = BabbagePParams
{ bppMinFeeA :: !(HKD f (CompactForm Coin))
{ bppMinFeeFactor :: !(HKD f CoinPerByte)
-- ^ The linear factor for the minimum fee calculation
, bppMinFeeB :: !(HKD f (CompactForm Coin))
, bppMinFeeConstant :: !(HKD f (CompactForm Coin))
-- ^ The constant factor for the minimum fee calculation
, bppMaxBBSize :: !(HKD f Word32)
-- ^ Maximal block body size
Expand Down Expand Up @@ -150,6 +136,14 @@ data BabbagePParams f era = BabbagePParams
}
deriving (Generic)

bppMinFeeA :: BabbagePParams f era -> HKD f CoinPerByte
bppMinFeeA = bppMinFeeFactor
{-# DEPRECATED bppMinFeeA "In favor of `bppMinFeeFactor`" #-}

bppMinFeeB :: BabbagePParams f era -> HKD f (CompactForm Coin)
bppMinFeeB = bppMinFeeConstant
{-# DEPRECATED bppMinFeeB "In favor of `bppMinFeeConstant`" #-}

deriving instance Eq (BabbagePParams Identity era)

deriving instance Ord (BabbagePParams Identity era)
Expand Down Expand Up @@ -186,8 +180,8 @@ instance EraPParams BabbageEra where
upgradePParamsHKD () = upgradeBabbagePParams True
downgradePParamsHKD = downgradeBabbagePParams

hkdMinFeeACompactL = lens bppMinFeeA $ \pp x -> pp {bppMinFeeA = x}
hkdMinFeeBCompactL = lens bppMinFeeB $ \pp x -> pp {bppMinFeeB = x}
hkdMinFeeFactorL = lens bppMinFeeFactor $ \pp x -> pp {bppMinFeeFactor = x}
hkdMinFeeConstantCompactL = lens bppMinFeeConstant $ \pp x -> pp {bppMinFeeConstant = x}
hkdMaxBBSizeL = lens bppMaxBBSize $ \pp x -> pp {bppMaxBBSize = x}
hkdMaxTxSizeL = lens bppMaxTxSize $ \pp x -> pp {bppMaxTxSize = x}
hkdMaxBHSizeL = lens bppMaxBHSize $ \pp x -> pp {bppMaxBHSize = x}
Expand All @@ -207,8 +201,8 @@ instance EraPParams BabbageEra where
hkdMinUTxOValueCompactL = notSupportedInThisEraL

eraPParams =
[ ppMinFeeA
, ppMinFeeB
[ ppMinFeeFactor
, ppMinFeeConstant
, ppMaxBBSize
, ppMaxTxSize
, ppMaxBHSize
Expand Down Expand Up @@ -268,8 +262,8 @@ instance EraGov BabbageEra where
emptyBabbagePParams :: forall era. Era era => BabbagePParams Identity era
emptyBabbagePParams =
BabbagePParams
{ bppMinFeeA = CompactCoin 0
, bppMinFeeB = CompactCoin 0
{ bppMinFeeFactor = CoinPerByte $ Coin 0
, bppMinFeeConstant = CompactCoin 0
, bppMaxBBSize = 0
, bppMaxTxSize = 2048
, bppMaxBHSize = 0
Expand All @@ -295,8 +289,8 @@ emptyBabbagePParams =
emptyBabbagePParamsUpdate :: BabbagePParams StrictMaybe era
emptyBabbagePParamsUpdate =
BabbagePParams
{ bppMinFeeA = SNothing
, bppMinFeeB = SNothing
{ bppMinFeeFactor = SNothing
, bppMinFeeConstant = SNothing
, bppMaxBBSize = SNothing
, bppMaxTxSize = SNothing
, bppMaxBHSize = SNothing
Expand Down Expand Up @@ -327,8 +321,8 @@ upgradeBabbagePParams ::
BabbagePParams f BabbageEra
upgradeBabbagePParams updateCoinsPerUTxOWord AlonzoPParams {..} =
BabbagePParams
{ bppMinFeeA = appMinFeeA
, bppMinFeeB = appMinFeeB
{ bppMinFeeFactor = appMinFeeFactor
, bppMinFeeConstant = appMinFeeConstant
, bppMaxBBSize = appMaxBBSize
, bppMaxTxSize = appMaxTxSize
, bppMaxBHSize = appMaxBHSize
Expand Down Expand Up @@ -366,8 +360,8 @@ downgradeBabbagePParams ::
PParamsHKD f AlonzoEra
downgradeBabbagePParams DowngradeBabbagePParams {..} BabbagePParams {..} =
AlonzoPParams
{ appMinFeeA = bppMinFeeA
, appMinFeeB = bppMinFeeB
{ appMinFeeFactor = bppMinFeeFactor
, appMinFeeConstant = bppMinFeeConstant
, appMaxBBSize = bppMaxBBSize
, appMaxTxSize = bppMaxTxSize
, appMaxBHSize = bppMaxBHSize
Expand Down
1 change: 0 additions & 1 deletion eras/babbage/impl/src/Cardano/Ledger/Babbage/TxOut.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,6 @@ import qualified Cardano.Ledger.Alonzo.TxBody as Alonzo
import Cardano.Ledger.Babbage.Era (BabbageEra)
import Cardano.Ledger.Babbage.PParams (
BabbageEraPParams (..),
CoinPerByte (..),
ppCoinsPerUTxOByteL,
)
import Cardano.Ledger.Babbage.Scripts ()
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -27,8 +27,6 @@ import Test.Cardano.Ledger.Alonzo.Arbitrary ()
import Test.Cardano.Ledger.Core.Arbitrary (genValidCostModels)
import Test.QuickCheck

deriving instance Arbitrary CoinPerByte

instance Arbitrary (BabbagePParams Identity era) where
arbitrary =
BabbagePParams
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -27,9 +27,6 @@ import Cardano.Ledger.Shelley.Rules
import qualified Data.TreeDiff.OMap as OMap
import Test.Cardano.Ledger.Alonzo.TreeDiff

-- Core
deriving newtype instance ToExpr CoinPerByte

-- Scripts
instance ToExpr (PlutusScript BabbageEra)

Expand Down
5 changes: 4 additions & 1 deletion eras/conway/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,13 @@

## 1.21.0.0

* Renamed:
- `cppMinFeeA` -> `cppMinFeeFactor`
- `cppMinFeeB` -> `cppMinFeeConstant`
* Changed type of `cppMinFeeA` to `CoinPerByte`
* Add `cddl` sub-library, and `generate-cddl` executable.
* Re-export `UtxoEnv` from `Cardano.Ledger.Conway.Rules.Utxo`
* Changed the type of the following fields to `CompactForm Coin` in `ConwayPParams`:
- `cppMinFeeA`
- `cppMinFeeB`
- `cppKeyDeposit`
- `cppMinPoolCost`
Expand Down
2 changes: 1 addition & 1 deletion eras/conway/impl/golden/pparams-update.json
Original file line number Diff line number Diff line change
Expand Up @@ -855,6 +855,6 @@
"stakePoolDeposit": 5863692308783077770,
"treasuryCut": 0.5,
"txFeeFixed": 86,
"txFeePerByte": 39,
"txFeePerByte": 67,
"utxoCostPerByte": 11
}
Loading