{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Cardano.Ledger.Mary
( MaryEra,
Self,
TxOut,
Value,
TxBody,
Script,
AuxiliaryData,
PParams,
PParamsDelta,
Tx,
)
where
import Cardano.Ledger.BaseTypes (BlocksMade (..))
import Cardano.Ledger.Crypto (Crypto)
import qualified Cardano.Ledger.Crypto as CC
import qualified Cardano.Ledger.Era as E (Era (Crypto))
import qualified Cardano.Ledger.Mary.Value as V (Value)
import Cardano.Ledger.Shelley.API hiding (TxBody)
import Cardano.Ledger.Shelley.EpochBoundary (emptySnapShots)
import Cardano.Ledger.Shelley.LedgerState (minfee)
import qualified Cardano.Ledger.Shelley.PParams as Shelley (PParamsUpdate)
import Cardano.Ledger.ShelleyMA
import Cardano.Ledger.ShelleyMA.Rules.EraMapping ()
import Cardano.Ledger.ShelleyMA.Rules.Utxo (consumed, scaledMinDeposit)
import Cardano.Ledger.ShelleyMA.Rules.Utxow ()
import Cardano.Ledger.ShelleyMA.Timelocks (Timelock)
import Cardano.Ledger.Val (Val ((<->)), coin, inject)
import Data.Default.Class (def)
import qualified Data.Map.Strict as Map
instance ShelleyEraCrypto c => ApplyTx (MaryEra c)
instance ShelleyEraCrypto c => ApplyBlock (MaryEra c)
instance Crypto c => CanStartFromGenesis (MaryEra c) where
initialState :: ShelleyGenesis (MaryEra c)
-> AdditionalGenesisConfig (MaryEra c) -> NewEpochState (MaryEra c)
initialState ShelleyGenesis (MaryEra c)
sg () =
EpochNo
-> BlocksMade (Crypto (MaryEra c))
-> BlocksMade (Crypto (MaryEra c))
-> EpochState (MaryEra c)
-> StrictMaybe (PulsingRewUpdate (Crypto (MaryEra c)))
-> PoolDistr (Crypto (MaryEra c))
-> StashedAVVMAddresses (MaryEra c)
-> NewEpochState (MaryEra c)
forall era.
EpochNo
-> BlocksMade (Crypto era)
-> BlocksMade (Crypto era)
-> EpochState era
-> StrictMaybe (PulsingRewUpdate (Crypto era))
-> PoolDistr (Crypto era)
-> StashedAVVMAddresses era
-> NewEpochState era
NewEpochState
EpochNo
initialEpochNo
(Map (KeyHash 'StakePool c) Natural -> BlocksMade c
forall crypto.
Map (KeyHash 'StakePool crypto) Natural -> BlocksMade crypto
BlocksMade Map (KeyHash 'StakePool c) Natural
forall k a. Map k a
Map.empty)
(Map (KeyHash 'StakePool c) Natural -> BlocksMade c
forall crypto.
Map (KeyHash 'StakePool crypto) Natural -> BlocksMade crypto
BlocksMade Map (KeyHash 'StakePool c) Natural
forall k a. Map k a
Map.empty)
( AccountState
-> SnapShots (Crypto (MaryEra c))
-> LedgerState (MaryEra c)
-> PParams (MaryEra c)
-> PParams (MaryEra c)
-> NonMyopic (Crypto (MaryEra c))
-> EpochState (MaryEra c)
forall era.
AccountState
-> SnapShots (Crypto era)
-> LedgerState era
-> PParams era
-> PParams era
-> NonMyopic (Crypto era)
-> EpochState era
EpochState
(Coin -> Coin -> AccountState
AccountState (Integer -> Coin
Coin Integer
0) Coin
reserves)
SnapShots (Crypto (MaryEra c))
forall crypto. SnapShots crypto
emptySnapShots
( UTxOState (MaryEra c)
-> DPState (Crypto (MaryEra c)) -> LedgerState (MaryEra c)
forall era.
UTxOState era -> DPState (Crypto era) -> LedgerState era
LedgerState
( UTxO (MaryEra c)
-> Coin
-> Coin
-> State (EraRule "PPUP" (MaryEra c))
-> IncrementalStake (Crypto (MaryEra c))
-> UTxOState (MaryEra c)
forall era.
UTxO era
-> Coin
-> Coin
-> State (EraRule "PPUP" era)
-> IncrementalStake (Crypto era)
-> UTxOState era
UTxOState
UTxO (MaryEra c)
initialUtxo
(Integer -> Coin
Coin Integer
0)
(Integer -> Coin
Coin Integer
0)
State (EraRule "PPUP" (MaryEra c))
forall a. Default a => a
def
(Map (Credential 'Staking c) Coin
-> Map Ptr Coin -> IncrementalStake c
forall crypto.
Map (Credential 'Staking crypto) Coin
-> Map Ptr Coin -> IncrementalStake crypto
IStake Map (Credential 'Staking c) Coin
forall a. Monoid a => a
mempty Map Ptr Coin
forall a. Monoid a => a
mempty)
)
(DState c -> PState c -> DPState c
forall crypto. DState crypto -> PState crypto -> DPState crypto
DPState (DState c
forall a. Default a => a
def {_genDelegs :: GenDelegs c
_genDelegs = Map (KeyHash 'Genesis c) (GenDelegPair c) -> GenDelegs c
forall crypto.
Map (KeyHash 'Genesis crypto) (GenDelegPair crypto)
-> GenDelegs crypto
GenDelegs Map (KeyHash 'Genesis c) (GenDelegPair c)
genDelegs}) PState c
forall a. Default a => a
def)
)
PParams (MaryEra c)
PParams (MaryEra c)
pp
PParams (MaryEra c)
PParams (MaryEra c)
pp
NonMyopic (Crypto (MaryEra c))
forall a. Default a => a
def
)
StrictMaybe (PulsingRewUpdate (Crypto (MaryEra c)))
forall a. StrictMaybe a
SNothing
(Map (KeyHash 'StakePool c) (IndividualPoolStake c) -> PoolDistr c
forall crypto.
Map (KeyHash 'StakePool crypto) (IndividualPoolStake crypto)
-> PoolDistr crypto
PoolDistr Map (KeyHash 'StakePool c) (IndividualPoolStake c)
forall k a. Map k a
Map.empty)
()
where
initialEpochNo :: EpochNo
initialEpochNo = EpochNo
0
initialUtxo :: UTxO (MaryEra c)
initialUtxo = ShelleyGenesis (MaryEra c) -> UTxO (MaryEra c)
forall era.
(Era era, UsesTxOut era) =>
ShelleyGenesis era -> UTxO era
genesisUTxO ShelleyGenesis (MaryEra c)
sg
reserves :: Coin
reserves =
Value c -> Coin
forall t. Val t => t -> Coin
coin (Value c -> Coin) -> Value c -> Coin
forall a b. (a -> b) -> a -> b
$
Coin -> Value c
forall t. Val t => Coin -> t
inject (Word64 -> Coin
word64ToCoin (ShelleyGenesis (MaryEra c) -> Word64
forall era. ShelleyGenesis era -> Word64
sgMaxLovelaceSupply ShelleyGenesis (MaryEra c)
sg))
Value c -> Value c -> Value c
forall t. Val t => t -> t -> t
<-> UTxO (MaryEra c) -> Value (MaryEra c)
forall era. Era era => UTxO era -> Value era
balance UTxO (MaryEra c)
initialUtxo
genDelegs :: Map
(KeyHash 'Genesis (Crypto (MaryEra c)))
(GenDelegPair (Crypto (MaryEra c)))
genDelegs = ShelleyGenesis (MaryEra c)
-> Map
(KeyHash 'Genesis (Crypto (MaryEra c)))
(GenDelegPair (Crypto (MaryEra c)))
forall era.
ShelleyGenesis era
-> Map (KeyHash 'Genesis (Crypto era)) (GenDelegPair (Crypto era))
sgGenDelegs ShelleyGenesis (MaryEra c)
sg
pp :: PParams (MaryEra c)
pp = ShelleyGenesis (MaryEra c) -> PParams (MaryEra c)
forall era. ShelleyGenesis era -> PParams era
sgProtocolParams ShelleyGenesis (MaryEra c)
sg
instance ShelleyEraCrypto c => ShelleyBasedEra (MaryEra c)
instance CC.Crypto c => CLI (MaryEra c) where
evaluateMinFee :: PParams (MaryEra c) -> Tx (MaryEra c) -> Coin
evaluateMinFee = PParams (MaryEra c) -> Tx (MaryEra c) -> Coin
forall pp tx.
(HasField "_minfeeA" pp Natural, HasField "_minfeeB" pp Natural,
HasField "txsize" tx Integer) =>
pp -> tx -> Coin
minfee
evaluateConsumed :: PParams (MaryEra c)
-> UTxO (MaryEra c) -> TxBody (MaryEra c) -> Value (MaryEra c)
evaluateConsumed = PParams (MaryEra c)
-> UTxO (MaryEra c) -> TxBody (MaryEra c) -> Value (MaryEra c)
forall era.
(Era era,
HasField "certs" (TxBody era) (StrictSeq (DCert (Crypto era))),
HasField "inputs" (TxBody era) (Set (TxIn (Crypto era))),
HasField "mint" (TxBody era) (Value era),
HasField "wdrls" (TxBody era) (Wdrl (Crypto era)),
HasField "_keyDeposit" (PParams era) Coin) =>
PParams era -> UTxO era -> TxBody era -> Value era
consumed
addKeyWitnesses :: Tx (MaryEra c)
-> Set (WitVKey 'Witness (Crypto (MaryEra c))) -> Tx (MaryEra c)
addKeyWitnesses = Tx (MaryEra c)
-> Set (WitVKey 'Witness (Crypto (MaryEra c))) -> Tx (MaryEra c)
forall era.
(Era era, Witnesses era ~ WitnessSet era,
AnnotatedData (Script era), ToCBOR (AuxiliaryData era),
ToCBOR (TxBody era)) =>
Tx era -> Set (WitVKey 'Witness (Crypto era)) -> Tx era
addShelleyKeyWitnesses
evaluateMinLovelaceOutput :: PParams (MaryEra c) -> TxOut (MaryEra c) -> Coin
evaluateMinLovelaceOutput PParams (MaryEra c)
pp (TxOut _ v) = Value c -> Coin -> Coin
forall v. Val v => v -> Coin -> Coin
scaledMinDeposit Value (MaryEra c)
Value c
v (PParams' Identity (MaryEra c) -> HKD Identity Coin
forall (f :: * -> *) era. PParams' f era -> HKD f Coin
_minUTxOValue PParams (MaryEra c)
PParams' Identity (MaryEra c)
pp)
type MaryEra c = ShelleyMAEra 'Mary c
type Self c = ShelleyMAEra 'Mary c
type Script era = Timelock (E.Crypto era)
type Value era = V.Value (E.Crypto era)
type PParamsDelta era = Shelley.PParamsUpdate era