{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# OPTIONS_GHC -Wno-orphans #-}

-- | This module contains the type of protocol parameters and EraPParams instance
module Cardano.Ledger.Babbage.PParams (
  BabbageEraPParams (..),
  CoinPerByte (..),
  ppCoinsPerUTxOByteL,
  ppuCoinsPerUTxOByteL,
  BabbagePParams (..),
  emptyBabbagePParams,
  emptyBabbagePParamsUpdate,
  DowngradeBabbagePParams (..),
  upgradeBabbagePParams,
  getLanguageView,
  LangDepView (..),
  encodeLangViews,
  coinsPerUTxOWordToCoinsPerUTxOByte,
  coinsPerUTxOByteToCoinsPerUTxOWord,
  babbagePParamsHKDPairs,
  babbageCommonPParamsHKDPairs,
)
where

import Cardano.Ledger.Alonzo (AlonzoEra)
import Cardano.Ledger.Alonzo.Core
import Cardano.Ledger.Alonzo.PParams (
  AlonzoEraPParams (..),
  AlonzoPParams (..),
  LangDepView (..),
  OrdExUnits (..),
  alonzoCommonPParamsHKDPairs,
  encodeLangViews,
  getLanguageView,
 )
import Cardano.Ledger.Alonzo.Scripts (
  CostModels,
  ExUnits (..),
  Prices (..),
  emptyCostModels,
 )
import Cardano.Ledger.Babbage.Era (BabbageEra)
import Cardano.Ledger.BaseTypes (
  EpochInterval (..),
  NonNegativeInterval,
  Nonce,
  ProtVer (..),
  StrictMaybe (..),
  UnitInterval,
  isSNothing,
 )
import Cardano.Ledger.Binary (
  DecCBOR (..),
  EncCBOR (..),
  Encoding,
  FromCBOR (..),
  ToCBOR (..),
  decCBORGroup,
  decodeRecordNamed,
  encCBORGroup,
  encodeListLen,
  listLen,
 )
import Cardano.Ledger.Binary.Coders (
  Decode (..),
  Density (..),
  Encode (..),
  Field (..),
  Wrapped (..),
  decode,
  encode,
  field,
  (!>),
 )
import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Core (EraPParams (..))
import Cardano.Ledger.Crypto (Crypto)
import Cardano.Ledger.HKD (HKD, HKDFunctor (..))
import Cardano.Ledger.Orphans ()
import Cardano.Ledger.Shelley.PParams (shelleyCommonPParamsHKDPairsV8)
import Control.DeepSeq (NFData)
import Data.Aeson as Aeson (
  FromJSON (..),
  Key,
  KeyValue ((.=)),
  ToJSON (..),
  Value,
  object,
  pairs,
  withObject,
  (.!=),
  (.:),
 )
import Data.Functor.Identity (Identity (..))
import Data.Proxy (Proxy (Proxy))
import Data.Word (Word16, Word32)
import GHC.Generics (Generic)
import Lens.Micro
import NoThunks.Class (NoThunks (..))
import Numeric.Natural (Natural)

newtype CoinPerByte = CoinPerByte {CoinPerByte -> Coin
unCoinPerByte :: Coin}
  deriving stock (CoinPerByte -> CoinPerByte -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CoinPerByte -> CoinPerByte -> Bool
$c/= :: CoinPerByte -> CoinPerByte -> Bool
== :: CoinPerByte -> CoinPerByte -> Bool
$c== :: CoinPerByte -> CoinPerByte -> Bool
Eq, Eq CoinPerByte
CoinPerByte -> CoinPerByte -> Bool
CoinPerByte -> CoinPerByte -> Ordering
CoinPerByte -> CoinPerByte -> CoinPerByte
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CoinPerByte -> CoinPerByte -> CoinPerByte
$cmin :: CoinPerByte -> CoinPerByte -> CoinPerByte
max :: CoinPerByte -> CoinPerByte -> CoinPerByte
$cmax :: CoinPerByte -> CoinPerByte -> CoinPerByte
>= :: CoinPerByte -> CoinPerByte -> Bool
$c>= :: CoinPerByte -> CoinPerByte -> Bool
> :: CoinPerByte -> CoinPerByte -> Bool
$c> :: CoinPerByte -> CoinPerByte -> Bool
<= :: CoinPerByte -> CoinPerByte -> Bool
$c<= :: CoinPerByte -> CoinPerByte -> Bool
< :: CoinPerByte -> CoinPerByte -> Bool
$c< :: CoinPerByte -> CoinPerByte -> Bool
compare :: CoinPerByte -> CoinPerByte -> Ordering
$ccompare :: CoinPerByte -> CoinPerByte -> Ordering
Ord)
  deriving newtype (Typeable CoinPerByte
CoinPerByte -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [CoinPerByte] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy CoinPerByte -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [CoinPerByte] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [CoinPerByte] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy CoinPerByte -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy CoinPerByte -> Size
encCBOR :: CoinPerByte -> Encoding
$cencCBOR :: CoinPerByte -> Encoding
EncCBOR, Typeable CoinPerByte
Proxy CoinPerByte -> Text
forall s. Decoder s CoinPerByte
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy CoinPerByte -> Decoder s ()
label :: Proxy CoinPerByte -> Text
$clabel :: Proxy CoinPerByte -> Text
dropCBOR :: forall s. Proxy CoinPerByte -> Decoder s ()
$cdropCBOR :: forall s. Proxy CoinPerByte -> Decoder s ()
decCBOR :: forall s. Decoder s CoinPerByte
$cdecCBOR :: forall s. Decoder s CoinPerByte
DecCBOR, [CoinPerByte] -> Encoding
[CoinPerByte] -> Value
CoinPerByte -> Bool
CoinPerByte -> Encoding
CoinPerByte -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: CoinPerByte -> Bool
$comitField :: CoinPerByte -> Bool
toEncodingList :: [CoinPerByte] -> Encoding
$ctoEncodingList :: [CoinPerByte] -> Encoding
toJSONList :: [CoinPerByte] -> Value
$ctoJSONList :: [CoinPerByte] -> Value
toEncoding :: CoinPerByte -> Encoding
$ctoEncoding :: CoinPerByte -> Encoding
toJSON :: CoinPerByte -> Value
$ctoJSON :: CoinPerByte -> Value
ToJSON, Maybe CoinPerByte
Value -> Parser [CoinPerByte]
Value -> Parser CoinPerByte
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
omittedField :: Maybe CoinPerByte
$comittedField :: Maybe CoinPerByte
parseJSONList :: Value -> Parser [CoinPerByte]
$cparseJSONList :: Value -> Parser [CoinPerByte]
parseJSON :: Value -> Parser CoinPerByte
$cparseJSON :: Value -> Parser CoinPerByte
FromJSON, CoinPerByte -> ()
forall a. (a -> ()) -> NFData a
rnf :: CoinPerByte -> ()
$crnf :: CoinPerByte -> ()
NFData, Context -> CoinPerByte -> IO (Maybe ThunkInfo)
Proxy CoinPerByte -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy CoinPerByte -> String
$cshowTypeOf :: Proxy CoinPerByte -> String
wNoThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo)
noThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo)
NoThunks, Int -> CoinPerByte -> ShowS
[CoinPerByte] -> ShowS
CoinPerByte -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CoinPerByte] -> ShowS
$cshowList :: [CoinPerByte] -> ShowS
show :: CoinPerByte -> String
$cshow :: CoinPerByte -> String
showsPrec :: Int -> CoinPerByte -> ShowS
$cshowsPrec :: Int -> CoinPerByte -> ShowS
Show)

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

ppCoinsPerUTxOByteL ::
  forall era. BabbageEraPParams era => Lens' (PParams era) CoinPerByte
ppCoinsPerUTxOByteL :: forall era.
BabbageEraPParams era =>
Lens' (PParams era) CoinPerByte
ppCoinsPerUTxOByteL = forall era. Lens' (PParams era) (PParamsHKD Identity era)
ppLens forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era (f :: * -> *).
(BabbageEraPParams era, HKDFunctor f) =>
Lens' (PParamsHKD f era) (HKD f CoinPerByte)
hkdCoinsPerUTxOByteL @era @Identity

ppuCoinsPerUTxOByteL ::
  forall era. BabbageEraPParams era => Lens' (PParamsUpdate era) (StrictMaybe CoinPerByte)
ppuCoinsPerUTxOByteL :: forall era.
BabbageEraPParams era =>
Lens' (PParamsUpdate era) (StrictMaybe CoinPerByte)
ppuCoinsPerUTxOByteL = forall era. Lens' (PParamsUpdate era) (PParamsHKD StrictMaybe era)
ppuLens forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era (f :: * -> *).
(BabbageEraPParams era, HKDFunctor f) =>
Lens' (PParamsHKD f era) (HKD f CoinPerByte)
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
  { forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinFeeA :: !(HKD f Coin)
  -- ^ The linear factor for the minimum fee calculation
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinFeeB :: !(HKD f Coin)
  -- ^ The constant factor for the minimum fee calculation
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMaxBBSize :: !(HKD f Word32)
  -- ^ Maximal block body size
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMaxTxSize :: !(HKD f Word32)
  -- ^ Maximal transaction size
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word16
bppMaxBHSize :: !(HKD f Word16)
  -- ^ Maximal block header size
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppKeyDeposit :: !(HKD f Coin)
  -- ^ The amount of a key registration deposit
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppPoolDeposit :: !(HKD f Coin)
  -- ^ The amount of a pool registration deposit
  , forall (f :: * -> *) era.
BabbagePParams f era -> HKD f EpochInterval
bppEMax :: !(HKD f EpochInterval)
  -- ^ Maximum number of epochs in the future a pool retirement is allowed to
  -- be scheduled for.
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppNOpt :: !(HKD f Natural)
  -- ^ Desired number of pools
  , forall (f :: * -> *) era.
BabbagePParams f era -> HKD f NonNegativeInterval
bppA0 :: !(HKD f NonNegativeInterval)
  -- ^ Pool influence
  , forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppRho :: !(HKD f UnitInterval)
  -- ^ Monetary expansion
  , forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppTau :: !(HKD f UnitInterval)
  -- ^ Treasury expansion
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f ProtVer
bppProtocolVersion :: !(HKD f ProtVer)
  -- ^ Protocol version
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinPoolCost :: !(HKD f Coin)
  -- ^ Minimum Stake Pool Cost
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f CoinPerByte
bppCoinsPerUTxOByte :: !(HKD f CoinPerByte)
  -- ^ Cost in lovelace per byte of UTxO storage (instead of bppCoinsPerUTxOByte)
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f CostModels
bppCostModels :: !(HKD f CostModels)
  -- ^ Cost models for non-native script languages
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Prices
bppPrices :: !(HKD f Prices)
  -- ^ Prices of execution units (for non-native script languages)
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppMaxTxExUnits :: !(HKD f OrdExUnits)
  -- ^ Max total script execution resources units allowed per tx
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppMaxBlockExUnits :: !(HKD f OrdExUnits)
  -- ^ Max total script execution resources units allowed per block
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxValSize :: !(HKD f Natural)
  -- ^ Max size of a Value in an output
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppCollateralPercentage :: !(HKD f Natural)
  -- ^ Percentage of the txfee which must be provided as collateral when
  -- including non-native scripts.
  , forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxCollateralInputs :: !(HKD f Natural)
  -- ^ Maximum number of collateral inputs allowed in a transaction
  }
  deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) era x.
Rep (BabbagePParams f era) x -> BabbagePParams f era
forall (f :: * -> *) era x.
BabbagePParams f era -> Rep (BabbagePParams f era) x
$cto :: forall (f :: * -> *) era x.
Rep (BabbagePParams f era) x -> BabbagePParams f era
$cfrom :: forall (f :: * -> *) era x.
BabbagePParams f era -> Rep (BabbagePParams f era) x
Generic)

deriving instance Eq (BabbagePParams Identity era)

deriving instance Ord (BabbagePParams Identity era)

deriving instance Show (BabbagePParams Identity era)

instance NoThunks (BabbagePParams Identity era)

instance NFData (BabbagePParams Identity era)

deriving instance Eq (BabbagePParams StrictMaybe era)

deriving instance Ord (BabbagePParams StrictMaybe era)

deriving instance Show (BabbagePParams StrictMaybe era)

instance NoThunks (BabbagePParams StrictMaybe era)

instance NFData (BabbagePParams StrictMaybe era)

data DowngradeBabbagePParams f = DowngradeBabbagePParams
  { forall (f :: * -> *).
DowngradeBabbagePParams f -> HKD f UnitInterval
dbppD :: !(HKD f UnitInterval)
  , forall (f :: * -> *). DowngradeBabbagePParams f -> HKD f Nonce
dbppExtraEntropy :: !(HKD f Nonce)
  }

instance Crypto c => EraPParams (BabbageEra c) where
  type PParamsHKD f (BabbageEra c) = BabbagePParams f (BabbageEra c)
  type UpgradePParams f (BabbageEra c) = ()
  type DowngradePParams f (BabbageEra c) = DowngradeBabbagePParams f

  emptyPParamsIdentity :: PParamsHKD Identity (BabbageEra c)
emptyPParamsIdentity = forall era. Era era => BabbagePParams Identity era
emptyBabbagePParams
  emptyPParamsStrictMaybe :: PParamsHKD StrictMaybe (BabbageEra c)
emptyPParamsStrictMaybe = forall era. BabbagePParams StrictMaybe era
emptyBabbagePParamsUpdate

  upgradePParamsHKD :: forall (f :: * -> *).
(HKDApplicative f, EraPParams (PreviousEra (BabbageEra c))) =>
UpgradePParams f (BabbageEra c)
-> PParamsHKD f (PreviousEra (BabbageEra c))
-> PParamsHKD f (BabbageEra c)
upgradePParamsHKD () = forall (f :: * -> *) c.
HKDFunctor f =>
Bool
-> PParamsHKD f (AlonzoEra c) -> BabbagePParams f (BabbageEra c)
upgradeBabbagePParams Bool
True
  downgradePParamsHKD :: forall (f :: * -> *).
(HKDFunctor f, EraPParams (PreviousEra (BabbageEra c))) =>
DowngradePParams f (BabbageEra c)
-> PParamsHKD f (BabbageEra c)
-> PParamsHKD f (PreviousEra (BabbageEra c))
downgradePParamsHKD = forall (f :: * -> *) c.
HKDFunctor f =>
DowngradeBabbagePParams f
-> BabbagePParams f (BabbageEra c) -> PParamsHKD f (AlonzoEra c)
downgradeBabbagePParams

  hkdMinFeeAL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Coin)
hkdMinFeeAL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinFeeA forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Coin
x -> PParamsHKD f (BabbageEra c)
pp {bppMinFeeA :: HKD f Coin
bppMinFeeA = HKD f Coin
x}
  hkdMinFeeBL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Coin)
hkdMinFeeBL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinFeeB forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Coin
x -> PParamsHKD f (BabbageEra c)
pp {bppMinFeeB :: HKD f Coin
bppMinFeeB = HKD f Coin
x}
  hkdMaxBBSizeL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Word32)
hkdMaxBBSizeL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMaxBBSize forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Word32
x -> PParamsHKD f (BabbageEra c)
pp {bppMaxBBSize :: HKD f Word32
bppMaxBBSize = HKD f Word32
x}
  hkdMaxTxSizeL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Word32)
hkdMaxTxSizeL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMaxTxSize forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Word32
x -> PParamsHKD f (BabbageEra c)
pp {bppMaxTxSize :: HKD f Word32
bppMaxTxSize = HKD f Word32
x}
  hkdMaxBHSizeL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Word16)
hkdMaxBHSizeL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word16
bppMaxBHSize forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Word16
x -> PParamsHKD f (BabbageEra c)
pp {bppMaxBHSize :: HKD f Word16
bppMaxBHSize = HKD f Word16
x}
  hkdKeyDepositL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Coin)
hkdKeyDepositL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppKeyDeposit forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Coin
x -> PParamsHKD f (BabbageEra c)
pp {bppKeyDeposit :: HKD f Coin
bppKeyDeposit = HKD f Coin
x}
  hkdPoolDepositL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Coin)
hkdPoolDepositL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppPoolDeposit forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Coin
x -> PParamsHKD f (BabbageEra c)
pp {bppPoolDeposit :: HKD f Coin
bppPoolDeposit = HKD f Coin
x}
  hkdEMaxL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f EpochInterval)
hkdEMaxL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era.
BabbagePParams f era -> HKD f EpochInterval
bppEMax forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f EpochInterval
x -> PParamsHKD f (BabbageEra c)
pp {bppEMax :: HKD f EpochInterval
bppEMax = HKD f EpochInterval
x}
  hkdNOptL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Natural)
hkdNOptL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppNOpt forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Natural
x -> PParamsHKD f (BabbageEra c)
pp {bppNOpt :: HKD f Natural
bppNOpt = HKD f Natural
x}
  hkdA0L :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f NonNegativeInterval)
hkdA0L = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era.
BabbagePParams f era -> HKD f NonNegativeInterval
bppA0 forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f NonNegativeInterval
x -> PParamsHKD f (BabbageEra c)
pp {bppA0 :: HKD f NonNegativeInterval
bppA0 = HKD f NonNegativeInterval
x}
  hkdRhoL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f UnitInterval)
hkdRhoL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppRho forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f UnitInterval
x -> PParamsHKD f (BabbageEra c)
pp {bppRho :: HKD f UnitInterval
bppRho = HKD f UnitInterval
x}
  hkdTauL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f UnitInterval)
hkdTauL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppTau forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f UnitInterval
x -> PParamsHKD f (BabbageEra c)
pp {bppTau :: HKD f UnitInterval
bppTau = HKD f UnitInterval
x}
  hkdProtocolVersionL :: forall (f :: * -> *).
(HKDFunctor f, ProtVerAtMost (BabbageEra c) 8) =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f ProtVer)
hkdProtocolVersionL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f ProtVer
bppProtocolVersion forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f ProtVer
x -> PParamsHKD f (BabbageEra c)
pp {bppProtocolVersion :: HKD f ProtVer
bppProtocolVersion = HKD f ProtVer
x}
  hkdMinPoolCostL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Coin)
hkdMinPoolCostL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinPoolCost forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Coin
x -> PParamsHKD f (BabbageEra c)
pp {bppMinPoolCost :: HKD f Coin
bppMinPoolCost = HKD f Coin
x}

  ppDG :: SimpleGetter (PParams (BabbageEra c)) UnitInterval
ppDG = forall s a. (s -> a) -> SimpleGetter s a
to (forall a b. a -> b -> a
const forall a. Bounded a => a
minBound)
  hkdDL :: forall (f :: * -> *).
(HKDFunctor f, ProtVerAtMost (BabbageEra c) 6) =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f UnitInterval)
hkdDL = forall a b. HasCallStack => Lens' a b
notSupportedInThisEraL
  hkdExtraEntropyL :: forall (f :: * -> *).
(HKDFunctor f, ProtVerAtMost (BabbageEra c) 6) =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Nonce)
hkdExtraEntropyL = forall a b. HasCallStack => Lens' a b
notSupportedInThisEraL
  hkdMinUTxOValueL :: forall (f :: * -> *).
(HKDFunctor f, ProtVerAtMost (BabbageEra c) 4) =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Coin)
hkdMinUTxOValueL = forall a b. HasCallStack => Lens' a b
notSupportedInThisEraL

instance Crypto c => AlonzoEraPParams (BabbageEra c) where
  hkdCoinsPerUTxOWordL :: forall (f :: * -> *).
(HKDFunctor f, ExactEra AlonzoEra (BabbageEra c)) =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f CoinPerWord)
hkdCoinsPerUTxOWordL = forall a b. HasCallStack => Lens' a b
notSupportedInThisEraL
  hkdCostModelsL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f CostModels)
hkdCostModelsL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f CostModels
bppCostModels forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f CostModels
x -> PParamsHKD f (BabbageEra c)
pp {bppCostModels :: HKD f CostModels
bppCostModels = HKD f CostModels
x}
  hkdPricesL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Prices)
hkdPricesL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Prices
bppPrices forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Prices
x -> PParamsHKD f (BabbageEra c)
pp {bppPrices :: HKD f Prices
bppPrices = HKD f Prices
x}
  hkdMaxTxExUnitsL :: forall f. HKDFunctor f => Lens' (PParamsHKD f (BabbageEra c)) (HKD f ExUnits)
  hkdMaxTxExUnitsL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f ExUnits)
hkdMaxTxExUnitsL =
    forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (forall (f :: * -> *) (proxy :: (* -> *) -> *) a b.
HKDFunctor f =>
proxy f -> (a -> b) -> HKD f a -> HKD f b
hkdMap (forall {k} (t :: k). Proxy t
Proxy @f) OrdExUnits -> ExUnits
unOrdExUnits forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppMaxTxExUnits) forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f ExUnits
x ->
      PParamsHKD f (BabbageEra c)
pp {bppMaxTxExUnits :: HKD f OrdExUnits
bppMaxTxExUnits = forall (f :: * -> *) (proxy :: (* -> *) -> *) a b.
HKDFunctor f =>
proxy f -> (a -> b) -> HKD f a -> HKD f b
hkdMap (forall {k} (t :: k). Proxy t
Proxy @f) ExUnits -> OrdExUnits
OrdExUnits HKD f ExUnits
x}
  hkdMaxBlockExUnitsL :: forall f. HKDFunctor f => Lens' (PParamsHKD f (BabbageEra c)) (HKD f ExUnits)
  hkdMaxBlockExUnitsL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f ExUnits)
hkdMaxBlockExUnitsL =
    forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (forall (f :: * -> *) (proxy :: (* -> *) -> *) a b.
HKDFunctor f =>
proxy f -> (a -> b) -> HKD f a -> HKD f b
hkdMap (forall {k} (t :: k). Proxy t
Proxy @f) OrdExUnits -> ExUnits
unOrdExUnits forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppMaxBlockExUnits) forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f ExUnits
x ->
      PParamsHKD f (BabbageEra c)
pp {bppMaxBlockExUnits :: HKD f OrdExUnits
bppMaxBlockExUnits = forall (f :: * -> *) (proxy :: (* -> *) -> *) a b.
HKDFunctor f =>
proxy f -> (a -> b) -> HKD f a -> HKD f b
hkdMap (forall {k} (t :: k). Proxy t
Proxy @f) ExUnits -> OrdExUnits
OrdExUnits HKD f ExUnits
x}
  hkdMaxValSizeL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Natural)
hkdMaxValSizeL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxValSize forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Natural
x -> PParamsHKD f (BabbageEra c)
pp {bppMaxValSize :: HKD f Natural
bppMaxValSize = HKD f Natural
x}
  hkdCollateralPercentageL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Natural)
hkdCollateralPercentageL =
    forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppCollateralPercentage forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Natural
x -> PParamsHKD f (BabbageEra c)
pp {bppCollateralPercentage :: HKD f Natural
bppCollateralPercentage = HKD f Natural
x}
  hkdMaxCollateralInputsL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f Natural)
hkdMaxCollateralInputsL =
    forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxCollateralInputs forall a b. (a -> b) -> a -> b
$ \PParamsHKD f (BabbageEra c)
pp HKD f Natural
x -> PParamsHKD f (BabbageEra c)
pp {bppMaxCollateralInputs :: HKD f Natural
bppMaxCollateralInputs = HKD f Natural
x}

instance Crypto c => BabbageEraPParams (BabbageEra c) where
  hkdCoinsPerUTxOByteL :: forall (f :: * -> *).
HKDFunctor f =>
Lens' (PParamsHKD f (BabbageEra c)) (HKD f CoinPerByte)
hkdCoinsPerUTxOByteL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era. BabbagePParams f era -> HKD f CoinPerByte
bppCoinsPerUTxOByte (\BabbagePParams f (BabbageEra c)
pp HKD f CoinPerByte
x -> BabbagePParams f (BabbageEra c)
pp {bppCoinsPerUTxOByte :: HKD f CoinPerByte
bppCoinsPerUTxOByte = HKD f CoinPerByte
x})

instance Crypto c => EraGov (BabbageEra c) where
  type GovState (BabbageEra c) = ShelleyGovState (BabbageEra c)
  emptyGovState :: GovState (BabbageEra c)
emptyGovState = forall era. EraPParams era => ShelleyGovState era
emptyShelleyGovState

  getProposedPPUpdates :: GovState (BabbageEra c) -> Maybe (ProposedPPUpdates (BabbageEra c))
getProposedPPUpdates = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. ShelleyGovState era -> ProposedPPUpdates era
sgsCurProposals

  curPParamsGovStateL :: Lens' (GovState (BabbageEra c)) (PParams (BabbageEra c))
curPParamsGovStateL = forall era. Lens' (ShelleyGovState era) (PParams era)
curPParamsShelleyGovStateL

  prevPParamsGovStateL :: Lens' (GovState (BabbageEra c)) (PParams (BabbageEra c))
prevPParamsGovStateL = forall era. Lens' (ShelleyGovState era) (PParams era)
prevPParamsShelleyGovStateL

  futurePParamsGovStateL :: Lens' (GovState (BabbageEra c)) (FuturePParams (BabbageEra c))
futurePParamsGovStateL = forall era. Lens' (ShelleyGovState era) (FuturePParams era)
futurePParamsShelleyGovStateL

  obligationGovState :: GovState (BabbageEra c) -> Obligations
obligationGovState = forall a b. a -> b -> a
const forall a. Monoid a => a
mempty

instance Era era => EncCBOR (BabbagePParams Identity era) where
  encCBOR :: BabbagePParams Identity era -> Encoding
encCBOR BabbagePParams {HKD Identity Natural
HKD Identity Word16
HKD Identity Word32
HKD Identity CostModels
HKD Identity Prices
HKD Identity OrdExUnits
HKD Identity Coin
HKD Identity ProtVer
HKD Identity NonNegativeInterval
HKD Identity UnitInterval
HKD Identity EpochInterval
HKD Identity CoinPerByte
bppMaxCollateralInputs :: HKD Identity Natural
bppCollateralPercentage :: HKD Identity Natural
bppMaxValSize :: HKD Identity Natural
bppMaxBlockExUnits :: HKD Identity OrdExUnits
bppMaxTxExUnits :: HKD Identity OrdExUnits
bppPrices :: HKD Identity Prices
bppCostModels :: HKD Identity CostModels
bppCoinsPerUTxOByte :: HKD Identity CoinPerByte
bppMinPoolCost :: HKD Identity Coin
bppProtocolVersion :: HKD Identity ProtVer
bppTau :: HKD Identity UnitInterval
bppRho :: HKD Identity UnitInterval
bppA0 :: HKD Identity NonNegativeInterval
bppNOpt :: HKD Identity Natural
bppEMax :: HKD Identity EpochInterval
bppPoolDeposit :: HKD Identity Coin
bppKeyDeposit :: HKD Identity Coin
bppMaxBHSize :: HKD Identity Word16
bppMaxTxSize :: HKD Identity Word32
bppMaxBBSize :: HKD Identity Word32
bppMinFeeB :: HKD Identity Coin
bppMinFeeA :: HKD Identity Coin
bppMaxCollateralInputs :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppCollateralPercentage :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxValSize :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxBlockExUnits :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppMaxTxExUnits :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppPrices :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Prices
bppCostModels :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f CostModels
bppCoinsPerUTxOByte :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f CoinPerByte
bppMinPoolCost :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppProtocolVersion :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f ProtVer
bppTau :: forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppRho :: forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppA0 :: forall (f :: * -> *) era.
BabbagePParams f era -> HKD f NonNegativeInterval
bppNOpt :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppEMax :: forall (f :: * -> *) era.
BabbagePParams f era -> HKD f EpochInterval
bppPoolDeposit :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppKeyDeposit :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMaxBHSize :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word16
bppMaxTxSize :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMaxBBSize :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMinFeeB :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinFeeA :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
..} =
    Word -> Encoding
encodeListLen (Word
21 forall a. Num a => a -> a -> a
+ forall a. EncCBORGroup a => a -> Word
listLen HKD Identity ProtVer
bppProtocolVersion)
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Coin
bppMinFeeA
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Coin
bppMinFeeB
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Word32
bppMaxBBSize
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Word32
bppMaxTxSize
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Word16
bppMaxBHSize
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Coin
bppKeyDeposit
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Coin
bppPoolDeposit
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity EpochInterval
bppEMax
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Natural
bppNOpt
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity NonNegativeInterval
bppA0
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity UnitInterval
bppRho
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity UnitInterval
bppTau
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBORGroup a => a -> Encoding
encCBORGroup HKD Identity ProtVer
bppProtocolVersion
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Coin
bppMinPoolCost
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity CoinPerByte
bppCoinsPerUTxOByte
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity CostModels
bppCostModels
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Prices
bppPrices
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity OrdExUnits
bppMaxTxExUnits
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity OrdExUnits
bppMaxBlockExUnits
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Natural
bppMaxValSize
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Natural
bppCollateralPercentage
      forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR HKD Identity Natural
bppMaxCollateralInputs

instance Era era => ToCBOR (BabbagePParams Identity era) where
  toCBOR :: BabbagePParams Identity era -> Encoding
toCBOR = forall era t. (Era era, EncCBOR t) => t -> Encoding
toEraCBOR @era

instance Era era => DecCBOR (BabbagePParams Identity era) where
  decCBOR :: forall s. Decoder s (BabbagePParams Identity era)
decCBOR =
    forall a s. Text -> (a -> Int) -> Decoder s a -> Decoder s a
decodeRecordNamed Text
"PParams" (\BabbagePParams Identity era
pp -> Int
21 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. EncCBORGroup a => a -> Word
listLen (forall (f :: * -> *) era. BabbagePParams f era -> HKD f ProtVer
bppProtocolVersion BabbagePParams Identity era
pp))) forall a b. (a -> b) -> a -> b
$ do
      Coin
bppMinFeeA <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Coin
bppMinFeeB <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Word32
bppMaxBBSize <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Word32
bppMaxTxSize <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Word16
bppMaxBHSize <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Coin
bppKeyDeposit <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Coin
bppPoolDeposit <- forall a s. DecCBOR a => Decoder s a
decCBOR
      EpochInterval
bppEMax <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Natural
bppNOpt <- forall a s. DecCBOR a => Decoder s a
decCBOR
      NonNegativeInterval
bppA0 <- forall a s. DecCBOR a => Decoder s a
decCBOR
      UnitInterval
bppRho <- forall a s. DecCBOR a => Decoder s a
decCBOR
      UnitInterval
bppTau <- forall a s. DecCBOR a => Decoder s a
decCBOR
      ProtVer
bppProtocolVersion <- forall a s. DecCBORGroup a => Decoder s a
decCBORGroup
      Coin
bppMinPoolCost <- forall a s. DecCBOR a => Decoder s a
decCBOR
      CoinPerByte
bppCoinsPerUTxOByte <- forall a s. DecCBOR a => Decoder s a
decCBOR
      CostModels
bppCostModels <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Prices
bppPrices <- forall a s. DecCBOR a => Decoder s a
decCBOR
      OrdExUnits
bppMaxTxExUnits <- forall a s. DecCBOR a => Decoder s a
decCBOR
      OrdExUnits
bppMaxBlockExUnits <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Natural
bppMaxValSize <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Natural
bppCollateralPercentage <- forall a s. DecCBOR a => Decoder s a
decCBOR
      Natural
bppMaxCollateralInputs <- forall a s. DecCBOR a => Decoder s a
decCBOR
      forall (f :: * -> *) a. Applicative f => a -> f a
pure BabbagePParams {Natural
Word16
Word32
CostModels
Prices
OrdExUnits
Coin
ProtVer
NonNegativeInterval
UnitInterval
EpochInterval
CoinPerByte
bppMaxCollateralInputs :: Natural
bppCollateralPercentage :: Natural
bppMaxValSize :: Natural
bppMaxBlockExUnits :: OrdExUnits
bppMaxTxExUnits :: OrdExUnits
bppPrices :: Prices
bppCostModels :: CostModels
bppCoinsPerUTxOByte :: CoinPerByte
bppMinPoolCost :: Coin
bppProtocolVersion :: ProtVer
bppTau :: UnitInterval
bppRho :: UnitInterval
bppA0 :: NonNegativeInterval
bppNOpt :: Natural
bppEMax :: EpochInterval
bppPoolDeposit :: Coin
bppKeyDeposit :: Coin
bppMaxBHSize :: Word16
bppMaxTxSize :: Word32
bppMaxBBSize :: Word32
bppMinFeeB :: Coin
bppMinFeeA :: Coin
bppMaxCollateralInputs :: HKD Identity Natural
bppCollateralPercentage :: HKD Identity Natural
bppMaxValSize :: HKD Identity Natural
bppMaxBlockExUnits :: HKD Identity OrdExUnits
bppMaxTxExUnits :: HKD Identity OrdExUnits
bppPrices :: HKD Identity Prices
bppCostModels :: HKD Identity CostModels
bppCoinsPerUTxOByte :: HKD Identity CoinPerByte
bppMinPoolCost :: HKD Identity Coin
bppProtocolVersion :: HKD Identity ProtVer
bppTau :: HKD Identity UnitInterval
bppRho :: HKD Identity UnitInterval
bppA0 :: HKD Identity NonNegativeInterval
bppNOpt :: HKD Identity Natural
bppEMax :: HKD Identity EpochInterval
bppPoolDeposit :: HKD Identity Coin
bppKeyDeposit :: HKD Identity Coin
bppMaxBHSize :: HKD Identity Word16
bppMaxTxSize :: HKD Identity Word32
bppMaxBBSize :: HKD Identity Word32
bppMinFeeB :: HKD Identity Coin
bppMinFeeA :: HKD Identity Coin
..}

instance Era era => FromCBOR (BabbagePParams Identity era) where
  fromCBOR :: forall s. Decoder s (BabbagePParams Identity era)
fromCBOR = forall era t s. (Era era, DecCBOR t) => Decoder s t
fromEraCBOR @era

instance
  (PParamsHKD Identity era ~ BabbagePParams Identity era, BabbageEraPParams era, ProtVerAtMost era 8) =>
  ToJSON (BabbagePParams Identity era)
  where
  toJSON :: BabbagePParams Identity era -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era a e.
(BabbageEraPParams era, KeyValue e a, ProtVerAtMost era 8) =>
PParamsHKD Identity era -> [a]
babbagePParamsPairs
  toEncoding :: BabbagePParams Identity era -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era a e.
(BabbageEraPParams era, KeyValue e a, ProtVerAtMost era 8) =>
PParamsHKD Identity era -> [a]
babbagePParamsPairs

babbagePParamsPairs ::
  forall era a e.
  (BabbageEraPParams era, KeyValue e a, ProtVerAtMost era 8) =>
  PParamsHKD Identity era ->
  [a]
babbagePParamsPairs :: forall era a e.
(BabbageEraPParams era, KeyValue e a, ProtVerAtMost era 8) =>
PParamsHKD Identity era -> [a]
babbagePParamsPairs PParamsHKD Identity era
pp =
  forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(.=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall era (f :: * -> *).
(BabbageEraPParams era, HKDFunctor f, ProtVerAtMost era 8) =>
Proxy f -> PParamsHKD f era -> [(Key, HKD f Value)]
babbagePParamsHKDPairs (forall {k} (t :: k). Proxy t
Proxy @Identity) PParamsHKD Identity era
pp

instance FromJSON (BabbagePParams Identity era) where
  parseJSON :: Value -> Parser (BabbagePParams Identity era)
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PParams" forall a b. (a -> b) -> a -> b
$ \Object
obj ->
      forall (f :: * -> *) era.
HKD f Coin
-> HKD f Coin
-> HKD f Word32
-> HKD f Word32
-> HKD f Word16
-> HKD f Coin
-> HKD f Coin
-> HKD f EpochInterval
-> HKD f Natural
-> HKD f NonNegativeInterval
-> HKD f UnitInterval
-> HKD f UnitInterval
-> HKD f ProtVer
-> HKD f Coin
-> HKD f CoinPerByte
-> HKD f CostModels
-> HKD f Prices
-> HKD f OrdExUnits
-> HKD f OrdExUnits
-> HKD f Natural
-> HKD f Natural
-> HKD f Natural
-> BabbagePParams f era
BabbagePParams
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"txFeePerByte"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"txFeeFixed"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxBlockBodySize"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxTxSize"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxBlockHeaderSize"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"stakeAddressDeposit"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"stakePoolDeposit"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"poolRetireMaxEpoch"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"stakePoolTargetNum"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"poolPledgeInfluence"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"monetaryExpansion"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"treasuryCut"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"protocolVersion"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"minPoolCost" forall a. Parser (Maybe a) -> a -> Parser a
.!= forall a. Monoid a => a
mempty
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"utxoCostPerByte"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"costModels"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"executionUnitPrices"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxTxExecutionUnits"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxBlockExecutionUnits"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxValueSize"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"collateralPercentage"
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxCollateralInputs"

-- | Returns a basic "empty" `PParams` structure with all zero values.
emptyBabbagePParams :: forall era. Era era => BabbagePParams Identity era
emptyBabbagePParams :: forall era. Era era => BabbagePParams Identity era
emptyBabbagePParams =
  BabbagePParams
    { bppMinFeeA :: HKD Identity Coin
bppMinFeeA = Integer -> Coin
Coin Integer
0
    , bppMinFeeB :: HKD Identity Coin
bppMinFeeB = Integer -> Coin
Coin Integer
0
    , bppMaxBBSize :: HKD Identity Word32
bppMaxBBSize = Word32
0
    , bppMaxTxSize :: HKD Identity Word32
bppMaxTxSize = Word32
2048
    , bppMaxBHSize :: HKD Identity Word16
bppMaxBHSize = Word16
0
    , bppKeyDeposit :: HKD Identity Coin
bppKeyDeposit = Integer -> Coin
Coin Integer
0
    , bppPoolDeposit :: HKD Identity Coin
bppPoolDeposit = Integer -> Coin
Coin Integer
0
    , bppEMax :: HKD Identity EpochInterval
bppEMax = Word32 -> EpochInterval
EpochInterval Word32
0
    , bppNOpt :: HKD Identity Natural
bppNOpt = Natural
100
    , bppA0 :: HKD Identity NonNegativeInterval
bppA0 = forall a. Bounded a => a
minBound
    , bppRho :: HKD Identity UnitInterval
bppRho = forall a. Bounded a => a
minBound
    , bppTau :: HKD Identity UnitInterval
bppTau = forall a. Bounded a => a
minBound
    , bppProtocolVersion :: HKD Identity ProtVer
bppProtocolVersion = Version -> Natural -> ProtVer
ProtVer (forall era. Era era => Version
eraProtVerLow @era) Natural
0
    , bppMinPoolCost :: HKD Identity Coin
bppMinPoolCost = forall a. Monoid a => a
mempty
    , bppCoinsPerUTxOByte :: HKD Identity CoinPerByte
bppCoinsPerUTxOByte = Coin -> CoinPerByte
CoinPerByte forall a b. (a -> b) -> a -> b
$ Integer -> Coin
Coin Integer
0
    , bppCostModels :: HKD Identity CostModels
bppCostModels = CostModels
emptyCostModels
    , bppPrices :: HKD Identity Prices
bppPrices = NonNegativeInterval -> NonNegativeInterval -> Prices
Prices forall a. Bounded a => a
minBound forall a. Bounded a => a
minBound
    , bppMaxTxExUnits :: HKD Identity OrdExUnits
bppMaxTxExUnits = ExUnits -> OrdExUnits
OrdExUnits forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> ExUnits
ExUnits Natural
0 Natural
0
    , bppMaxBlockExUnits :: HKD Identity OrdExUnits
bppMaxBlockExUnits = ExUnits -> OrdExUnits
OrdExUnits forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> ExUnits
ExUnits Natural
0 Natural
0
    , bppMaxValSize :: HKD Identity Natural
bppMaxValSize = Natural
0
    , bppCollateralPercentage :: HKD Identity Natural
bppCollateralPercentage = Natural
150
    , bppMaxCollateralInputs :: HKD Identity Natural
bppMaxCollateralInputs = Natural
5
    }

emptyBabbagePParamsUpdate :: BabbagePParams StrictMaybe era
emptyBabbagePParamsUpdate :: forall era. BabbagePParams StrictMaybe era
emptyBabbagePParamsUpdate =
  BabbagePParams
    { bppMinFeeA :: HKD StrictMaybe Coin
bppMinFeeA = forall a. StrictMaybe a
SNothing
    , bppMinFeeB :: HKD StrictMaybe Coin
bppMinFeeB = forall a. StrictMaybe a
SNothing
    , bppMaxBBSize :: HKD StrictMaybe Word32
bppMaxBBSize = forall a. StrictMaybe a
SNothing
    , bppMaxTxSize :: HKD StrictMaybe Word32
bppMaxTxSize = forall a. StrictMaybe a
SNothing
    , bppMaxBHSize :: HKD StrictMaybe Word16
bppMaxBHSize = forall a. StrictMaybe a
SNothing
    , bppKeyDeposit :: HKD StrictMaybe Coin
bppKeyDeposit = forall a. StrictMaybe a
SNothing
    , bppPoolDeposit :: HKD StrictMaybe Coin
bppPoolDeposit = forall a. StrictMaybe a
SNothing
    , bppEMax :: HKD StrictMaybe EpochInterval
bppEMax = forall a. StrictMaybe a
SNothing
    , bppNOpt :: HKD StrictMaybe Natural
bppNOpt = forall a. StrictMaybe a
SNothing
    , bppA0 :: HKD StrictMaybe NonNegativeInterval
bppA0 = forall a. StrictMaybe a
SNothing
    , bppRho :: HKD StrictMaybe UnitInterval
bppRho = forall a. StrictMaybe a
SNothing
    , bppTau :: HKD StrictMaybe UnitInterval
bppTau = forall a. StrictMaybe a
SNothing
    , bppProtocolVersion :: HKD StrictMaybe ProtVer
bppProtocolVersion = forall a. StrictMaybe a
SNothing
    , bppMinPoolCost :: HKD StrictMaybe Coin
bppMinPoolCost = forall a. StrictMaybe a
SNothing
    , bppCoinsPerUTxOByte :: HKD StrictMaybe CoinPerByte
bppCoinsPerUTxOByte = forall a. StrictMaybe a
SNothing
    , bppCostModels :: HKD StrictMaybe CostModels
bppCostModels = forall a. StrictMaybe a
SNothing
    , bppPrices :: HKD StrictMaybe Prices
bppPrices = forall a. StrictMaybe a
SNothing
    , bppMaxTxExUnits :: HKD StrictMaybe OrdExUnits
bppMaxTxExUnits = forall a. StrictMaybe a
SNothing
    , bppMaxBlockExUnits :: HKD StrictMaybe OrdExUnits
bppMaxBlockExUnits = forall a. StrictMaybe a
SNothing
    , bppMaxValSize :: HKD StrictMaybe Natural
bppMaxValSize = forall a. StrictMaybe a
SNothing
    , bppCollateralPercentage :: HKD StrictMaybe Natural
bppCollateralPercentage = forall a. StrictMaybe a
SNothing
    , bppMaxCollateralInputs :: HKD StrictMaybe Natural
bppMaxCollateralInputs = forall a. StrictMaybe a
SNothing
    }

-- =======================================================
-- A PParamsUpdate has StrictMaybe fields, we want to Sparse encode it, by
-- writing only those fields where the field is (SJust x), that is the role of
-- the local function (omitStrictMaybe key x)

encodePParamsUpdate ::
  BabbagePParams StrictMaybe era ->
  Encode ('Closed 'Sparse) (BabbagePParams StrictMaybe era)
encodePParamsUpdate :: forall era.
BabbagePParams StrictMaybe era
-> Encode ('Closed 'Sparse) (BabbagePParams StrictMaybe era)
encodePParamsUpdate BabbagePParams StrictMaybe era
ppup =
  forall t. t -> Encode ('Closed 'Sparse) t
Keyed forall (f :: * -> *) era.
HKD f Coin
-> HKD f Coin
-> HKD f Word32
-> HKD f Word32
-> HKD f Word16
-> HKD f Coin
-> HKD f Coin
-> HKD f EpochInterval
-> HKD f Natural
-> HKD f NonNegativeInterval
-> HKD f UnitInterval
-> HKD f UnitInterval
-> HKD f ProtVer
-> HKD f Coin
-> HKD f CoinPerByte
-> HKD f CostModels
-> HKD f Prices
-> HKD f OrdExUnits
-> HKD f OrdExUnits
-> HKD f Natural
-> HKD f Natural
-> HKD f Natural
-> BabbagePParams f era
BabbagePParams
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
0 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinFeeA BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
1 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinFeeB BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
2 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMaxBBSize BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
3 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMaxTxSize BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
4 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word16
bppMaxBHSize BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
5 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppKeyDeposit BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
6 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppPoolDeposit BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
7 (forall (f :: * -> *) era.
BabbagePParams f era -> HKD f EpochInterval
bppEMax BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
8 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppNOpt BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
9 (forall (f :: * -> *) era.
BabbagePParams f era -> HKD f NonNegativeInterval
bppA0 BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
10 (forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppRho BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
11 (forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppTau BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
14 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f ProtVer
bppProtocolVersion BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
16 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinPoolCost BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
17 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f CoinPerByte
bppCoinsPerUTxOByte BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
18 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f CostModels
bppCostModels BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
19 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Prices
bppPrices BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
20 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppMaxTxExUnits BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
21 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppMaxBlockExUnits BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
22 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxValSize BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
23 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppCollateralPercentage BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
    forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
24 (forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxCollateralInputs BabbagePParams StrictMaybe era
ppup) forall a. EncCBOR a => a -> Encoding
encCBOR
  where
    omitStrictMaybe ::
      Word -> StrictMaybe a -> (a -> Encoding) -> Encode ('Closed 'Sparse) (StrictMaybe a)
    omitStrictMaybe :: forall a.
Word
-> StrictMaybe a
-> (a -> Encoding)
-> Encode ('Closed 'Sparse) (StrictMaybe a)
omitStrictMaybe Word
key StrictMaybe a
x a -> Encoding
enc = forall t.
(t -> Bool)
-> Encode ('Closed 'Sparse) t -> Encode ('Closed 'Sparse) t
Omit forall a. StrictMaybe a -> Bool
isSNothing (forall t.
Word -> Encode ('Closed 'Dense) t -> Encode ('Closed 'Sparse) t
Key Word
key (forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (a -> Encoding
enc forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. StrictMaybe a -> a
fromSJust) StrictMaybe a
x))

    fromSJust :: StrictMaybe a -> a
    fromSJust :: forall a. StrictMaybe a -> a
fromSJust (SJust a
x) = a
x
    fromSJust StrictMaybe a
SNothing = forall a. HasCallStack => String -> a
error String
"SNothing in fromSJust. This should never happen, it is guarded by isSNothing."

instance Era era => EncCBOR (BabbagePParams StrictMaybe era) where
  encCBOR :: BabbagePParams StrictMaybe era -> Encoding
encCBOR BabbagePParams StrictMaybe era
ppup = forall (w :: Wrapped) t. Encode w t -> Encoding
encode (forall era.
BabbagePParams StrictMaybe era
-> Encode ('Closed 'Sparse) (BabbagePParams StrictMaybe era)
encodePParamsUpdate BabbagePParams StrictMaybe era
ppup)

updateField :: Word -> Field (BabbagePParams StrictMaybe era)
updateField :: forall era. Word -> Field (BabbagePParams StrictMaybe era)
updateField Word
0 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Coin
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMinFeeA :: HKD StrictMaybe Coin
bppMinFeeA = forall a. a -> StrictMaybe a
SJust Coin
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
1 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Coin
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMinFeeB :: HKD StrictMaybe Coin
bppMinFeeB = forall a. a -> StrictMaybe a
SJust Coin
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
2 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Word32
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMaxBBSize :: HKD StrictMaybe Word32
bppMaxBBSize = forall a. a -> StrictMaybe a
SJust Word32
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
3 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Word32
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMaxTxSize :: HKD StrictMaybe Word32
bppMaxTxSize = forall a. a -> StrictMaybe a
SJust Word32
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
4 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Word16
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMaxBHSize :: HKD StrictMaybe Word16
bppMaxBHSize = forall a. a -> StrictMaybe a
SJust Word16
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
5 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Coin
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppKeyDeposit :: HKD StrictMaybe Coin
bppKeyDeposit = forall a. a -> StrictMaybe a
SJust Coin
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
6 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Coin
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppPoolDeposit :: HKD StrictMaybe Coin
bppPoolDeposit = forall a. a -> StrictMaybe a
SJust Coin
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
7 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\EpochInterval
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppEMax :: HKD StrictMaybe EpochInterval
bppEMax = forall a. a -> StrictMaybe a
SJust EpochInterval
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
8 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Natural
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppNOpt :: HKD StrictMaybe Natural
bppNOpt = forall a. a -> StrictMaybe a
SJust Natural
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
9 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\NonNegativeInterval
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppA0 :: HKD StrictMaybe NonNegativeInterval
bppA0 = forall a. a -> StrictMaybe a
SJust NonNegativeInterval
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
10 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\UnitInterval
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppRho :: HKD StrictMaybe UnitInterval
bppRho = forall a. a -> StrictMaybe a
SJust UnitInterval
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
11 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\UnitInterval
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppTau :: HKD StrictMaybe UnitInterval
bppTau = forall a. a -> StrictMaybe a
SJust UnitInterval
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
14 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\ProtVer
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppProtocolVersion :: HKD StrictMaybe ProtVer
bppProtocolVersion = forall a. a -> StrictMaybe a
SJust ProtVer
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
16 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Coin
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMinPoolCost :: HKD StrictMaybe Coin
bppMinPoolCost = forall a. a -> StrictMaybe a
SJust Coin
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
17 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\CoinPerByte
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppCoinsPerUTxOByte :: HKD StrictMaybe CoinPerByte
bppCoinsPerUTxOByte = forall a. a -> StrictMaybe a
SJust CoinPerByte
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
18 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\CostModels
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppCostModels :: HKD StrictMaybe CostModels
bppCostModels = forall a. a -> StrictMaybe a
SJust CostModels
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
19 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Prices
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppPrices :: HKD StrictMaybe Prices
bppPrices = forall a. a -> StrictMaybe a
SJust Prices
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
20 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\OrdExUnits
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMaxTxExUnits :: HKD StrictMaybe OrdExUnits
bppMaxTxExUnits = forall a. a -> StrictMaybe a
SJust OrdExUnits
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
21 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\OrdExUnits
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMaxBlockExUnits :: HKD StrictMaybe OrdExUnits
bppMaxBlockExUnits = forall a. a -> StrictMaybe a
SJust OrdExUnits
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
22 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Natural
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMaxValSize :: HKD StrictMaybe Natural
bppMaxValSize = forall a. a -> StrictMaybe a
SJust Natural
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
23 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Natural
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppCollateralPercentage :: HKD StrictMaybe Natural
bppCollateralPercentage = forall a. a -> StrictMaybe a
SJust Natural
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
24 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Natural
x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up {bppMaxCollateralInputs :: HKD StrictMaybe Natural
bppMaxCollateralInputs = forall a. a -> StrictMaybe a
SJust Natural
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
updateField Word
k = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Any
_x BabbagePParams StrictMaybe era
up -> BabbagePParams StrictMaybe era
up) (forall (w :: Wrapped) t. Word -> Decode w t
Invalid Word
k)

instance Era era => DecCBOR (BabbagePParams StrictMaybe era) where
  decCBOR :: forall s. Decoder s (BabbagePParams StrictMaybe era)
decCBOR =
    forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode
      (forall t.
Typeable t =>
String
-> t
-> (Word -> Field t)
-> [(Word, String)]
-> Decode ('Closed 'Dense) t
SparseKeyed String
"PParamsUpdate" forall era. BabbagePParams StrictMaybe era
emptyBabbagePParamsUpdate forall era. Word -> Field (BabbagePParams StrictMaybe era)
updateField [])

instance Era era => ToCBOR (BabbagePParams StrictMaybe era) where
  toCBOR :: BabbagePParams StrictMaybe era -> Encoding
toCBOR = forall era t. (Era era, EncCBOR t) => t -> Encoding
toEraCBOR @era

instance Era era => FromCBOR (BabbagePParams StrictMaybe era) where
  fromCBOR :: forall s. Decoder s (BabbagePParams StrictMaybe era)
fromCBOR = forall era t s. (Era era, DecCBOR t) => Decoder s t
fromEraCBOR @era

instance
  ( PParamsHKD StrictMaybe era ~ BabbagePParams StrictMaybe era
  , BabbageEraPParams era
  , ProtVerAtMost era 8
  ) =>
  ToJSON (BabbagePParams StrictMaybe era)
  where
  toJSON :: BabbagePParams StrictMaybe era -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era a e.
(BabbageEraPParams era, KeyValue e a, ProtVerAtMost era 8) =>
PParamsHKD StrictMaybe era -> [a]
babbagePParamsUpdatePairs
  toEncoding :: BabbagePParams StrictMaybe era -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era a e.
(BabbageEraPParams era, KeyValue e a, ProtVerAtMost era 8) =>
PParamsHKD StrictMaybe era -> [a]
babbagePParamsUpdatePairs

babbagePParamsUpdatePairs ::
  forall era a e.
  (BabbageEraPParams era, KeyValue e a, ProtVerAtMost era 8) =>
  PParamsHKD StrictMaybe era ->
  [a]
babbagePParamsUpdatePairs :: forall era a e.
(BabbageEraPParams era, KeyValue e a, ProtVerAtMost era 8) =>
PParamsHKD StrictMaybe era -> [a]
babbagePParamsUpdatePairs PParamsHKD StrictMaybe era
pp =
  [ Key
k forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Value
v
  | (Key
k, SJust Value
v) <- forall era (f :: * -> *).
(BabbageEraPParams era, HKDFunctor f, ProtVerAtMost era 8) =>
Proxy f -> PParamsHKD f era -> [(Key, HKD f Value)]
babbagePParamsHKDPairs (forall {k} (t :: k). Proxy t
Proxy @StrictMaybe) PParamsHKD StrictMaybe era
pp
  ]

babbagePParamsHKDPairs ::
  forall era f.
  (BabbageEraPParams era, HKDFunctor f, ProtVerAtMost era 8) =>
  Proxy f ->
  PParamsHKD f era ->
  [(Key, HKD f Aeson.Value)]
babbagePParamsHKDPairs :: forall era (f :: * -> *).
(BabbageEraPParams era, HKDFunctor f, ProtVerAtMost era 8) =>
Proxy f -> PParamsHKD f era -> [(Key, HKD f Value)]
babbagePParamsHKDPairs Proxy f
px PParamsHKD f era
pp =
  forall era (f :: * -> *).
(BabbageEraPParams era, HKDFunctor f) =>
Proxy f -> PParamsHKD f era -> [(Key, HKD f Value)]
babbageCommonPParamsHKDPairs Proxy f
px PParamsHKD f era
pp
    forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) era.
(HKDFunctor f, EraPParams era, ProtVerAtMost era 8) =>
Proxy f -> PParamsHKD f era -> [(Key, HKD f Value)]
shelleyCommonPParamsHKDPairsV8 Proxy f
px PParamsHKD f era
pp -- for "protocolVersion"

-- | These are the fields that are common across all eras starting with Babbage.
babbageCommonPParamsHKDPairs ::
  forall era f.
  (BabbageEraPParams era, HKDFunctor f) =>
  Proxy f ->
  PParamsHKD f era ->
  [(Key, HKD f Aeson.Value)]
babbageCommonPParamsHKDPairs :: forall era (f :: * -> *).
(BabbageEraPParams era, HKDFunctor f) =>
Proxy f -> PParamsHKD f era -> [(Key, HKD f Value)]
babbageCommonPParamsHKDPairs Proxy f
px PParamsHKD f era
pp =
  forall (f :: * -> *) era.
(HKDFunctor f, AlonzoEraPParams era) =>
Proxy f -> PParamsHKD f era -> [(Key, HKD f Value)]
alonzoCommonPParamsHKDPairs Proxy f
px PParamsHKD f era
pp
    forall a. Semigroup a => a -> a -> a
<> [(Key
"utxoCostPerByte", forall (f :: * -> *) (proxy :: (* -> *) -> *) a b.
HKDFunctor f =>
proxy f -> (a -> b) -> HKD f a -> HKD f b
hkdMap Proxy f
px (forall a. ToJSON a => a -> Value
toJSON @CoinPerByte) (PParamsHKD f era
pp forall s a. s -> Getting a s a -> a
^. forall era (f :: * -> *).
(BabbageEraPParams era, HKDFunctor f) =>
Lens' (PParamsHKD f era) (HKD f CoinPerByte)
hkdCoinsPerUTxOByteL @_ @f))]

upgradeBabbagePParams ::
  forall f c.
  HKDFunctor f =>
  Bool ->
  PParamsHKD f (AlonzoEra c) ->
  BabbagePParams f (BabbageEra c)
upgradeBabbagePParams :: forall (f :: * -> *) c.
HKDFunctor f =>
Bool
-> PParamsHKD f (AlonzoEra c) -> BabbagePParams f (BabbageEra c)
upgradeBabbagePParams Bool
updateCoinsPerUTxOWord AlonzoPParams {HKD f Natural
HKD f Word16
HKD f Word32
HKD f CostModels
HKD f Prices
HKD f CoinPerWord
HKD f OrdExUnits
HKD f Coin
HKD f ProtVer
HKD f NonNegativeInterval
HKD f UnitInterval
HKD f Nonce
HKD f EpochInterval
appMinFeeA :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Coin
appMinFeeB :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Coin
appMaxBBSize :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Word32
appMaxTxSize :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Word32
appMaxBHSize :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Word16
appKeyDeposit :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Coin
appPoolDeposit :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Coin
appEMax :: forall (f :: * -> *) era.
AlonzoPParams f era -> HKD f EpochInterval
appNOpt :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Natural
appA0 :: forall (f :: * -> *) era.
AlonzoPParams f era -> HKD f NonNegativeInterval
appRho :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f UnitInterval
appTau :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f UnitInterval
appD :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f UnitInterval
appExtraEntropy :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Nonce
appProtocolVersion :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f ProtVer
appMinPoolCost :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Coin
appCoinsPerUTxOWord :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f CoinPerWord
appCostModels :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f CostModels
appPrices :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Prices
appMaxTxExUnits :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f OrdExUnits
appMaxBlockExUnits :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f OrdExUnits
appMaxValSize :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Natural
appCollateralPercentage :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Natural
appMaxCollateralInputs :: forall (f :: * -> *) era. AlonzoPParams f era -> HKD f Natural
appMaxCollateralInputs :: HKD f Natural
appCollateralPercentage :: HKD f Natural
appMaxValSize :: HKD f Natural
appMaxBlockExUnits :: HKD f OrdExUnits
appMaxTxExUnits :: HKD f OrdExUnits
appPrices :: HKD f Prices
appCostModels :: HKD f CostModels
appCoinsPerUTxOWord :: HKD f CoinPerWord
appMinPoolCost :: HKD f Coin
appProtocolVersion :: HKD f ProtVer
appExtraEntropy :: HKD f Nonce
appD :: HKD f UnitInterval
appTau :: HKD f UnitInterval
appRho :: HKD f UnitInterval
appA0 :: HKD f NonNegativeInterval
appNOpt :: HKD f Natural
appEMax :: HKD f EpochInterval
appPoolDeposit :: HKD f Coin
appKeyDeposit :: HKD f Coin
appMaxBHSize :: HKD f Word16
appMaxTxSize :: HKD f Word32
appMaxBBSize :: HKD f Word32
appMinFeeB :: HKD f Coin
appMinFeeA :: HKD f Coin
..} =
  BabbagePParams
    { bppMinFeeA :: HKD f Coin
bppMinFeeA = HKD f Coin
appMinFeeA
    , bppMinFeeB :: HKD f Coin
bppMinFeeB = HKD f Coin
appMinFeeB
    , bppMaxBBSize :: HKD f Word32
bppMaxBBSize = HKD f Word32
appMaxBBSize
    , bppMaxTxSize :: HKD f Word32
bppMaxTxSize = HKD f Word32
appMaxTxSize
    , bppMaxBHSize :: HKD f Word16
bppMaxBHSize = HKD f Word16
appMaxBHSize
    , bppKeyDeposit :: HKD f Coin
bppKeyDeposit = HKD f Coin
appKeyDeposit
    , bppPoolDeposit :: HKD f Coin
bppPoolDeposit = HKD f Coin
appPoolDeposit
    , bppEMax :: HKD f EpochInterval
bppEMax = HKD f EpochInterval
appEMax
    , bppNOpt :: HKD f Natural
bppNOpt = HKD f Natural
appNOpt
    , bppA0 :: HKD f NonNegativeInterval
bppA0 = HKD f NonNegativeInterval
appA0
    , bppRho :: HKD f UnitInterval
bppRho = HKD f UnitInterval
appRho
    , bppTau :: HKD f UnitInterval
bppTau = HKD f UnitInterval
appTau
    , bppProtocolVersion :: HKD f ProtVer
bppProtocolVersion = HKD f ProtVer
appProtocolVersion
    , bppMinPoolCost :: HKD f Coin
bppMinPoolCost = HKD f Coin
appMinPoolCost
    , bppCoinsPerUTxOByte :: HKD f CoinPerByte
bppCoinsPerUTxOByte =
        forall (f :: * -> *) (proxy :: (* -> *) -> *) a b.
HKDFunctor f =>
proxy f -> (a -> b) -> HKD f a -> HKD f b
hkdMap
          (forall {k} (t :: k). Proxy t
Proxy @f)
          ( if Bool
updateCoinsPerUTxOWord
              then CoinPerWord -> CoinPerByte
coinsPerUTxOWordToCoinsPerUTxOByte
              else CoinPerWord -> CoinPerByte
coinsPerUTxOWordToCoinsPerUTxOByteInTx
          )
          HKD f CoinPerWord
appCoinsPerUTxOWord
    , bppCostModels :: HKD f CostModels
bppCostModels = HKD f CostModels
appCostModels
    , bppPrices :: HKD f Prices
bppPrices = HKD f Prices
appPrices
    , bppMaxTxExUnits :: HKD f OrdExUnits
bppMaxTxExUnits = HKD f OrdExUnits
appMaxTxExUnits
    , bppMaxBlockExUnits :: HKD f OrdExUnits
bppMaxBlockExUnits = HKD f OrdExUnits
appMaxBlockExUnits
    , bppMaxValSize :: HKD f Natural
bppMaxValSize = HKD f Natural
appMaxValSize
    , bppCollateralPercentage :: HKD f Natural
bppCollateralPercentage = HKD f Natural
appCollateralPercentage
    , bppMaxCollateralInputs :: HKD f Natural
bppMaxCollateralInputs = HKD f Natural
appMaxCollateralInputs
    }

downgradeBabbagePParams ::
  forall f c.
  HKDFunctor f =>
  DowngradeBabbagePParams f ->
  BabbagePParams f (BabbageEra c) ->
  PParamsHKD f (AlonzoEra c)
downgradeBabbagePParams :: forall (f :: * -> *) c.
HKDFunctor f =>
DowngradeBabbagePParams f
-> BabbagePParams f (BabbageEra c) -> PParamsHKD f (AlonzoEra c)
downgradeBabbagePParams DowngradeBabbagePParams {HKD f UnitInterval
HKD f Nonce
dbppExtraEntropy :: HKD f Nonce
dbppD :: HKD f UnitInterval
dbppExtraEntropy :: forall (f :: * -> *). DowngradeBabbagePParams f -> HKD f Nonce
dbppD :: forall (f :: * -> *).
DowngradeBabbagePParams f -> HKD f UnitInterval
..} BabbagePParams {HKD f Natural
HKD f Word16
HKD f Word32
HKD f CostModels
HKD f Prices
HKD f OrdExUnits
HKD f Coin
HKD f ProtVer
HKD f NonNegativeInterval
HKD f UnitInterval
HKD f EpochInterval
HKD f CoinPerByte
bppMaxCollateralInputs :: HKD f Natural
bppCollateralPercentage :: HKD f Natural
bppMaxValSize :: HKD f Natural
bppMaxBlockExUnits :: HKD f OrdExUnits
bppMaxTxExUnits :: HKD f OrdExUnits
bppPrices :: HKD f Prices
bppCostModels :: HKD f CostModels
bppCoinsPerUTxOByte :: HKD f CoinPerByte
bppMinPoolCost :: HKD f Coin
bppProtocolVersion :: HKD f ProtVer
bppTau :: HKD f UnitInterval
bppRho :: HKD f UnitInterval
bppA0 :: HKD f NonNegativeInterval
bppNOpt :: HKD f Natural
bppEMax :: HKD f EpochInterval
bppPoolDeposit :: HKD f Coin
bppKeyDeposit :: HKD f Coin
bppMaxBHSize :: HKD f Word16
bppMaxTxSize :: HKD f Word32
bppMaxBBSize :: HKD f Word32
bppMinFeeB :: HKD f Coin
bppMinFeeA :: HKD f Coin
bppMaxCollateralInputs :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppCollateralPercentage :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxValSize :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppMaxBlockExUnits :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppMaxTxExUnits :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f OrdExUnits
bppPrices :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Prices
bppCostModels :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f CostModels
bppCoinsPerUTxOByte :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f CoinPerByte
bppMinPoolCost :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppProtocolVersion :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f ProtVer
bppTau :: forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppRho :: forall (f :: * -> *) era.
BabbagePParams f era -> HKD f UnitInterval
bppA0 :: forall (f :: * -> *) era.
BabbagePParams f era -> HKD f NonNegativeInterval
bppNOpt :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Natural
bppEMax :: forall (f :: * -> *) era.
BabbagePParams f era -> HKD f EpochInterval
bppPoolDeposit :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppKeyDeposit :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMaxBHSize :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word16
bppMaxTxSize :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMaxBBSize :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Word32
bppMinFeeB :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
bppMinFeeA :: forall (f :: * -> *) era. BabbagePParams f era -> HKD f Coin
..} =
  AlonzoPParams
    { appMinFeeA :: HKD f Coin
appMinFeeA = HKD f Coin
bppMinFeeA
    , appMinFeeB :: HKD f Coin
appMinFeeB = HKD f Coin
bppMinFeeB
    , appMaxBBSize :: HKD f Word32
appMaxBBSize = HKD f Word32
bppMaxBBSize
    , appMaxTxSize :: HKD f Word32
appMaxTxSize = HKD f Word32
bppMaxTxSize
    , appMaxBHSize :: HKD f Word16
appMaxBHSize = HKD f Word16
bppMaxBHSize
    , appKeyDeposit :: HKD f Coin
appKeyDeposit = HKD f Coin
bppKeyDeposit
    , appPoolDeposit :: HKD f Coin
appPoolDeposit = HKD f Coin
bppPoolDeposit
    , appEMax :: HKD f EpochInterval
appEMax = HKD f EpochInterval
bppEMax
    , appNOpt :: HKD f Natural
appNOpt = HKD f Natural
bppNOpt
    , appA0 :: HKD f NonNegativeInterval
appA0 = HKD f NonNegativeInterval
bppA0
    , appRho :: HKD f UnitInterval
appRho = HKD f UnitInterval
bppRho
    , appTau :: HKD f UnitInterval
appTau = HKD f UnitInterval
bppTau
    , appD :: HKD f UnitInterval
appD = HKD f UnitInterval
dbppD
    , appExtraEntropy :: HKD f Nonce
appExtraEntropy = HKD f Nonce
dbppExtraEntropy
    , appProtocolVersion :: HKD f ProtVer
appProtocolVersion = HKD f ProtVer
bppProtocolVersion
    , appMinPoolCost :: HKD f Coin
appMinPoolCost = HKD f Coin
bppMinPoolCost
    , appCoinsPerUTxOWord :: HKD f CoinPerWord
appCoinsPerUTxOWord = forall (f :: * -> *) (proxy :: (* -> *) -> *) a b.
HKDFunctor f =>
proxy f -> (a -> b) -> HKD f a -> HKD f b
hkdMap (forall {k} (t :: k). Proxy t
Proxy @f) CoinPerByte -> CoinPerWord
coinsPerUTxOByteToCoinsPerUTxOWord HKD f CoinPerByte
bppCoinsPerUTxOByte
    , appCostModels :: HKD f CostModels
appCostModels = HKD f CostModels
bppCostModels
    , appPrices :: HKD f Prices
appPrices = HKD f Prices
bppPrices
    , appMaxTxExUnits :: HKD f OrdExUnits
appMaxTxExUnits = HKD f OrdExUnits
bppMaxTxExUnits
    , appMaxBlockExUnits :: HKD f OrdExUnits
appMaxBlockExUnits = HKD f OrdExUnits
bppMaxBlockExUnits
    , appMaxValSize :: HKD f Natural
appMaxValSize = HKD f Natural
bppMaxValSize
    , appCollateralPercentage :: HKD f Natural
appCollateralPercentage = HKD f Natural
bppCollateralPercentage
    , appMaxCollateralInputs :: HKD f Natural
appMaxCollateralInputs = HKD f Natural
bppMaxCollateralInputs
    }

-- | A word is 8 bytes, so convert from coinsPerUTxOWord to coinsPerUTxOByte, rounding down.
coinsPerUTxOWordToCoinsPerUTxOByte :: CoinPerWord -> CoinPerByte
coinsPerUTxOWordToCoinsPerUTxOByte :: CoinPerWord -> CoinPerByte
coinsPerUTxOWordToCoinsPerUTxOByte (CoinPerWord (Coin Integer
c)) = Coin -> CoinPerByte
CoinPerByte forall a b. (a -> b) -> a -> b
$ Integer -> Coin
Coin forall a b. (a -> b) -> a -> b
$ Integer
c forall a. Integral a => a -> a -> a
`div` Integer
8

-- | A word is 8 bytes, so convert from coinsPerUTxOByte to coinsPerUTxOWord.
coinsPerUTxOByteToCoinsPerUTxOWord :: CoinPerByte -> CoinPerWord
coinsPerUTxOByteToCoinsPerUTxOWord :: CoinPerByte -> CoinPerWord
coinsPerUTxOByteToCoinsPerUTxOWord (CoinPerByte (Coin Integer
c)) = Coin -> CoinPerWord
CoinPerWord forall a b. (a -> b) -> a -> b
$ Integer -> Coin
Coin forall a b. (a -> b) -> a -> b
$ Integer
c forall a. Num a => a -> a -> a
* Integer
8

-- | Naively convert coins per UTxO word to coins per byte. This function only
-- exists to support the very unusual case of translating a transaction
-- containing an update to the 'coinsPerUTxOWord' field, in which case we must
-- not do the translation above, since this would render the transaction
-- invalid.
coinsPerUTxOWordToCoinsPerUTxOByteInTx :: CoinPerWord -> CoinPerByte
coinsPerUTxOWordToCoinsPerUTxOByteInTx :: CoinPerWord -> CoinPerByte
coinsPerUTxOWordToCoinsPerUTxOByteInTx (CoinPerWord (Coin Integer
c)) = Coin -> CoinPerByte
CoinPerByte forall a b. (a -> b) -> a -> b
$ Integer -> Coin
Coin Integer
c