{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Cardano.Ledger.Alonzo.Genesis (
AlonzoGenesis (
AlonzoGenesisWrapper,
unAlonzoGenesisWrapper,
AlonzoGenesis,
agCoinsPerUTxOWord,
agCostModels,
agPrices,
agMaxTxExUnits,
agMaxBlockExUnits,
agMaxValSize,
agCollateralPercentage,
agMaxCollateralInputs
),
toAlonzoGenesisPairs,
)
where
import Cardano.Ledger.Alonzo.Era (AlonzoEra)
import Cardano.Ledger.Alonzo.PParams (CoinPerWord, UpgradeAlonzoPParams (..))
import Cardano.Ledger.Alonzo.Scripts (CostModels, ExUnits (..), Prices (..))
import Cardano.Ledger.Binary (
DecCBOR,
EncCBOR,
FromCBOR (..),
ToCBOR (..),
)
import Cardano.Ledger.Binary.Coders (
Decode (From, RecD),
Encode (Rec, To),
decode,
encode,
(!>),
(<!),
)
import Cardano.Ledger.Core
import Cardano.Ledger.Crypto (Crypto, StandardCrypto)
import Cardano.Ledger.Genesis (EraGenesis (..))
import Data.Aeson (FromJSON (..), ToJSON (..), object, pairs, (.:), (.=))
import qualified Data.Aeson as Aeson
import Data.Functor.Identity (Identity)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks)
import Numeric.Natural (Natural)
newtype AlonzoGenesis = AlonzoGenesisWrapper
{ AlonzoGenesis -> UpgradeAlonzoPParams Identity
unAlonzoGenesisWrapper :: UpgradeAlonzoPParams Identity
}
deriving stock (AlonzoGenesis -> AlonzoGenesis -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AlonzoGenesis -> AlonzoGenesis -> Bool
$c/= :: AlonzoGenesis -> AlonzoGenesis -> Bool
== :: AlonzoGenesis -> AlonzoGenesis -> Bool
$c== :: AlonzoGenesis -> AlonzoGenesis -> Bool
Eq, forall x. Rep AlonzoGenesis x -> AlonzoGenesis
forall x. AlonzoGenesis -> Rep AlonzoGenesis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AlonzoGenesis x -> AlonzoGenesis
$cfrom :: forall x. AlonzoGenesis -> Rep AlonzoGenesis x
Generic)
deriving newtype (Int -> AlonzoGenesis -> ShowS
[AlonzoGenesis] -> ShowS
AlonzoGenesis -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AlonzoGenesis] -> ShowS
$cshowList :: [AlonzoGenesis] -> ShowS
show :: AlonzoGenesis -> String
$cshow :: AlonzoGenesis -> String
showsPrec :: Int -> AlonzoGenesis -> ShowS
$cshowsPrec :: Int -> AlonzoGenesis -> ShowS
Show, Context -> AlonzoGenesis -> IO (Maybe ThunkInfo)
Proxy AlonzoGenesis -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy AlonzoGenesis -> String
$cshowTypeOf :: Proxy AlonzoGenesis -> String
wNoThunks :: Context -> AlonzoGenesis -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> AlonzoGenesis -> IO (Maybe ThunkInfo)
noThunks :: Context -> AlonzoGenesis -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> AlonzoGenesis -> IO (Maybe ThunkInfo)
NoThunks)
pattern AlonzoGenesis ::
CoinPerWord ->
CostModels ->
Prices ->
ExUnits ->
ExUnits ->
Natural ->
Natural ->
Natural ->
AlonzoGenesis
pattern $bAlonzoGenesis :: CoinPerWord
-> CostModels
-> Prices
-> ExUnits
-> ExUnits
-> Natural
-> Natural
-> Natural
-> AlonzoGenesis
$mAlonzoGenesis :: forall {r}.
AlonzoGenesis
-> (CoinPerWord
-> CostModels
-> Prices
-> ExUnits
-> ExUnits
-> Natural
-> Natural
-> Natural
-> r)
-> ((# #) -> r)
-> r
AlonzoGenesis
{ AlonzoGenesis -> CoinPerWord
agCoinsPerUTxOWord
, AlonzoGenesis -> CostModels
agCostModels
, AlonzoGenesis -> Prices
agPrices
, AlonzoGenesis -> ExUnits
agMaxTxExUnits
, AlonzoGenesis -> ExUnits
agMaxBlockExUnits
, AlonzoGenesis -> Natural
agMaxValSize
, AlonzoGenesis -> Natural
agCollateralPercentage
, AlonzoGenesis -> Natural
agMaxCollateralInputs
} <-
( unAlonzoGenesisWrapper ->
UpgradeAlonzoPParams
{ uappCoinsPerUTxOWord = agCoinsPerUTxOWord
, uappCostModels = agCostModels
, uappPrices = agPrices
, uappMaxTxExUnits = agMaxTxExUnits
, uappMaxBlockExUnits = agMaxBlockExUnits
, uappMaxValSize = agMaxValSize
, uappCollateralPercentage = agCollateralPercentage
, uappMaxCollateralInputs = agMaxCollateralInputs
}
)
where
AlonzoGenesis
CoinPerWord
coinsPerUTxOWord_
CostModels
costModels_
Prices
prices_
ExUnits
maxTxExUnits_
ExUnits
maxBlockExUnits_
Natural
maxValSize_
Natural
collateralPercentage_
Natural
maxCollateralInputs_ =
UpgradeAlonzoPParams Identity -> AlonzoGenesis
AlonzoGenesisWrapper forall a b. (a -> b) -> a -> b
$
UpgradeAlonzoPParams
{ uappCoinsPerUTxOWord :: HKD Identity CoinPerWord
uappCoinsPerUTxOWord = CoinPerWord
coinsPerUTxOWord_
, uappCostModels :: HKD Identity CostModels
uappCostModels = CostModels
costModels_
, uappPrices :: HKD Identity Prices
uappPrices = Prices
prices_
, uappMaxTxExUnits :: HKD Identity ExUnits
uappMaxTxExUnits = ExUnits
maxTxExUnits_
, uappMaxBlockExUnits :: HKD Identity ExUnits
uappMaxBlockExUnits = ExUnits
maxBlockExUnits_
, uappMaxValSize :: HKD Identity Natural
uappMaxValSize = Natural
maxValSize_
, uappCollateralPercentage :: HKD Identity Natural
uappCollateralPercentage = Natural
collateralPercentage_
, uappMaxCollateralInputs :: HKD Identity Natural
uappMaxCollateralInputs = Natural
maxCollateralInputs_
}
{-# COMPLETE AlonzoGenesis #-}
instance Crypto c => EraGenesis (AlonzoEra c) where
type Genesis (AlonzoEra c) = AlonzoGenesis
instance DecCBOR AlonzoGenesis
instance EncCBOR AlonzoGenesis
instance FromCBOR AlonzoGenesis where
fromCBOR :: forall s. Decoder s AlonzoGenesis
fromCBOR =
forall era t s. Era era => Decoder s t -> Decoder s t
eraDecoder @(AlonzoEra StandardCrypto) forall a b. (a -> b) -> a -> b
$
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD CoinPerWord
-> CostModels
-> Prices
-> ExUnits
-> ExUnits
-> Natural
-> Natural
-> Natural
-> AlonzoGenesis
AlonzoGenesis
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
instance ToCBOR AlonzoGenesis where
toCBOR :: AlonzoGenesis -> Encoding
toCBOR
AlonzoGenesis
{ CoinPerWord
agCoinsPerUTxOWord :: CoinPerWord
agCoinsPerUTxOWord :: AlonzoGenesis -> CoinPerWord
agCoinsPerUTxOWord
, CostModels
agCostModels :: CostModels
agCostModels :: AlonzoGenesis -> CostModels
agCostModels
, Prices
agPrices :: Prices
agPrices :: AlonzoGenesis -> Prices
agPrices
, ExUnits
agMaxTxExUnits :: ExUnits
agMaxTxExUnits :: AlonzoGenesis -> ExUnits
agMaxTxExUnits
, ExUnits
agMaxBlockExUnits :: ExUnits
agMaxBlockExUnits :: AlonzoGenesis -> ExUnits
agMaxBlockExUnits
, Natural
agMaxValSize :: Natural
agMaxValSize :: AlonzoGenesis -> Natural
agMaxValSize
, Natural
agCollateralPercentage :: Natural
agCollateralPercentage :: AlonzoGenesis -> Natural
agCollateralPercentage
, Natural
agMaxCollateralInputs :: Natural
agMaxCollateralInputs :: AlonzoGenesis -> Natural
agMaxCollateralInputs
} =
forall era t. (Era era, EncCBOR t) => t -> Encoding
toEraCBOR @(AlonzoEra StandardCrypto)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (w :: Wrapped) t. Encode w t -> Encoding
encode
forall a b. (a -> b) -> a -> b
$ forall t. t -> Encode ('Closed 'Dense) t
Rec CoinPerWord
-> CostModels
-> Prices
-> ExUnits
-> ExUnits
-> Natural
-> Natural
-> Natural
-> AlonzoGenesis
AlonzoGenesis
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To CoinPerWord
agCoinsPerUTxOWord
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To CostModels
agCostModels
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Prices
agPrices
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To ExUnits
agMaxTxExUnits
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To ExUnits
agMaxBlockExUnits
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Natural
agMaxValSize
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Natural
agCollateralPercentage
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Natural
agMaxCollateralInputs
instance FromJSON AlonzoGenesis where
parseJSON :: Value -> Parser AlonzoGenesis
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"Alonzo Genesis" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
CoinPerWord
agCoinsPerUTxOWord <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"lovelacePerUTxOWord"
CostModels
agCostModels <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"costModels"
Prices
agPrices <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"executionPrices"
ExUnits
agMaxTxExUnits <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxTxExUnits"
ExUnits
agMaxBlockExUnits <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxBlockExUnits"
Natural
agMaxValSize <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxValueSize"
Natural
agCollateralPercentage <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"collateralPercentage"
Natural
agMaxCollateralInputs <- Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"maxCollateralInputs"
forall (m :: * -> *) a. Monad m => a -> m a
return AlonzoGenesis {Natural
ExUnits
Prices
CostModels
CoinPerWord
agMaxCollateralInputs :: Natural
agCollateralPercentage :: Natural
agMaxValSize :: Natural
agMaxBlockExUnits :: ExUnits
agMaxTxExUnits :: ExUnits
agPrices :: Prices
agCostModels :: CostModels
agCoinsPerUTxOWord :: CoinPerWord
agMaxCollateralInputs :: Natural
agCollateralPercentage :: Natural
agMaxValSize :: Natural
agMaxBlockExUnits :: ExUnits
agMaxTxExUnits :: ExUnits
agPrices :: Prices
agCostModels :: CostModels
agCoinsPerUTxOWord :: CoinPerWord
..}
instance ToJSON AlonzoGenesis where
toJSON :: AlonzoGenesis -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a. KeyValue e a => AlonzoGenesis -> [a]
toAlonzoGenesisPairs
toEncoding :: AlonzoGenesis -> 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 e a. KeyValue e a => AlonzoGenesis -> [a]
toAlonzoGenesisPairs
toAlonzoGenesisPairs :: Aeson.KeyValue e a => AlonzoGenesis -> [a]
toAlonzoGenesisPairs :: forall e a. KeyValue e a => AlonzoGenesis -> [a]
toAlonzoGenesisPairs AlonzoGenesis
ag =
[ Key
"lovelacePerUTxOWord" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AlonzoGenesis -> CoinPerWord
agCoinsPerUTxOWord AlonzoGenesis
ag
, Key
"costModels" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AlonzoGenesis -> CostModels
agCostModels AlonzoGenesis
ag
, Key
"executionPrices" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AlonzoGenesis -> Prices
agPrices AlonzoGenesis
ag
, Key
"maxTxExUnits" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AlonzoGenesis -> ExUnits
agMaxTxExUnits AlonzoGenesis
ag
, Key
"maxBlockExUnits" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AlonzoGenesis -> ExUnits
agMaxBlockExUnits AlonzoGenesis
ag
, Key
"maxValueSize" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AlonzoGenesis -> Natural
agMaxValSize AlonzoGenesis
ag
, Key
"collateralPercentage" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AlonzoGenesis -> Natural
agCollateralPercentage AlonzoGenesis
ag
, Key
"maxCollateralInputs" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= AlonzoGenesis -> Natural
agMaxCollateralInputs AlonzoGenesis
ag
]