Skip to content

Commit

Permalink
Merge pull request #4737 from IntersectMBO/lehins/remove-deprecated-a…
Browse files Browse the repository at this point in the history
…nd-unused

Remove deprecated and unused definitions
  • Loading branch information
lehins authored Nov 5, 2024
2 parents ddae517 + 10d9acf commit 78b20b6
Show file tree
Hide file tree
Showing 105 changed files with 188 additions and 1,612 deletions.
12 changes: 1 addition & 11 deletions eras/allegra/impl/src/Cardano/Ledger/Allegra.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,8 +2,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
-- CanStartFromGenesis
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Cardano.Ledger.Allegra (
Expand All @@ -23,13 +21,8 @@ import Cardano.Ledger.Allegra.TxSeq ()
import Cardano.Ledger.Allegra.UTxO ()
import Cardano.Ledger.Core
import Cardano.Ledger.Crypto (Crypto, StandardCrypto)
import Cardano.Ledger.Genesis (NoGenesis (..))
import Cardano.Ledger.Keys (DSignable, Hash)
import Cardano.Ledger.Shelley.API (
ApplyBlock,
ApplyTx,
CanStartFromGenesis (fromShelleyPParams),
)
import Cardano.Ledger.Shelley.API (ApplyBlock, ApplyTx)

type Allegra = AllegraEra StandardCrypto

Expand All @@ -44,6 +37,3 @@ instance
instance
(Crypto c, DSignable c (Hash c EraIndependentTxBody)) =>
ApplyBlock (AllegraEra c)

instance Crypto c => CanStartFromGenesis (AllegraEra c) where
fromShelleyPParams _ = translateEra' NoGenesis
8 changes: 8 additions & 0 deletions eras/alonzo/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,14 @@

## 1.12.0.0

* Remove deprecated `lookupPlutusScript`
* Remove deprecated `translateTxOut`, `requiredSignersAreWitnessed`
* Remove deprecated `getCoin`, `minfee`, `getMapFromValue`, `indexRedeemers` and `isTwoPhaseScriptAddressFromMap`
* Remove deprecated `AuxiliaryData`, `TxSeq`, `hashTxSeq` and `getAlonzoSpendingTxIn`
* Remove deprecated `alonzoGenesisAesonPairs`, `coinsPerUTxOWord`, `costmdls`, `prices`, `maxTxExUnits`, `maxBlockExUnits`, `maxValSize`, `collateralPercentage` and `maxCollateralInputs`
* Remove deprecated module `Cardano.Ledger.Alonzo.Data`
* Remove deprecated module `Cardano.Ledger.Alonzo.Scripts.Data`
* Remove deprecated module `Cardano.Ledger.Alonzo.Language`
* Use `Mismatch` to clarify predicate failures. #4711

### `testlib`
Expand Down
3 changes: 0 additions & 3 deletions eras/alonzo/impl/cardano-ledger-alonzo.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -29,17 +29,14 @@ library
exposed-modules:
Cardano.Ledger.Alonzo
Cardano.Ledger.Alonzo.Core
Cardano.Ledger.Alonzo.Data
Cardano.Ledger.Alonzo.Transition
Cardano.Ledger.Alonzo.Genesis
Cardano.Ledger.Alonzo.Language
Cardano.Ledger.Alonzo.Plutus.Context
Cardano.Ledger.Alonzo.Plutus.Evaluate
Cardano.Ledger.Alonzo.Plutus.TxInfo
Cardano.Ledger.Alonzo.PParams
Cardano.Ledger.Alonzo.Rules
Cardano.Ledger.Alonzo.Scripts
Cardano.Ledger.Alonzo.Scripts.Data
Cardano.Ledger.Alonzo.Translation
Cardano.Ledger.Alonzo.Tx
Cardano.Ledger.Alonzo.TxAuxData
Expand Down
25 changes: 7 additions & 18 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,9 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
-- CanStartFromGenesis
{-# OPTIONS_GHC -Wno-deprecations #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Cardano.Ledger.Alonzo (
Expand All @@ -23,7 +19,6 @@ module Cardano.Ledger.Alonzo (
where

import Cardano.Ledger.Alonzo.Era
import Cardano.Ledger.Alonzo.Genesis
import Cardano.Ledger.Alonzo.PParams ()
import Cardano.Ledger.Alonzo.Plutus.TxInfo ()
import Cardano.Ledger.Alonzo.Rules ()
Expand All @@ -35,15 +30,13 @@ import Cardano.Ledger.Alonzo.TxAuxData (AlonzoTxAuxData)
import Cardano.Ledger.Alonzo.TxBody (AlonzoTxBody, AlonzoTxOut)
import Cardano.Ledger.Alonzo.TxWits ()
import Cardano.Ledger.Alonzo.UTxO ()
import Cardano.Ledger.BaseTypes (Globals)
import Cardano.Ledger.Core
import Cardano.Ledger.Crypto (Crypto, StandardCrypto)
import Cardano.Ledger.Keys (DSignable, Hash)
import Cardano.Ledger.Keys (DSignable)
import Cardano.Ledger.Mary.Value (MaryValue)
import Cardano.Ledger.Plutus.Data ()
import Cardano.Ledger.Rules.ValidationMode (applySTSNonStatic)
import qualified Cardano.Ledger.Shelley.API as API
import Cardano.Ledger.Shelley.API.Mempool
import Cardano.Ledger.Shelley.API
import Control.Arrow (left)
import Control.Monad.Except (MonadError, liftEither)
import Control.Monad.Reader (runReader)
Expand All @@ -55,7 +48,7 @@ type Alonzo = AlonzoEra StandardCrypto

reapplyAlonzoTx ::
forall era m.
(API.ApplyTx era, MonadError (ApplyTxError era) m) =>
(ApplyTx era, MonadError (ApplyTxError era) m) =>
Globals ->
MempoolEnv era ->
MempoolState era ->
Expand All @@ -66,14 +59,10 @@ reapplyAlonzoTx globals env state vtx =
flip runReader globals
. applySTSNonStatic
@(EraRule "LEDGER" era)
$ TRC (env, state, API.extractTx vtx)
in liftEither . left API.ApplyTxError $ res
$ TRC (env, state, extractTx vtx)
in liftEither . left ApplyTxError $ res

instance (Crypto c, DSignable c (Hash c EraIndependentTxBody)) => API.ApplyTx (AlonzoEra c) where
instance (Crypto c, DSignable c (Hash c EraIndependentTxBody)) => ApplyTx (AlonzoEra c) where
reapplyTx = reapplyAlonzoTx

instance (Crypto c, DSignable c (Hash c EraIndependentTxBody)) => API.ApplyBlock (AlonzoEra c)

instance Crypto c => API.CanStartFromGenesis (AlonzoEra c) where
type AdditionalGenesisConfig (AlonzoEra c) = AlonzoGenesis
fromShelleyPParams ag = translateEra' ag . API.fromShelleyPParams ()
instance (Crypto c, DSignable c (Hash c EraIndependentTxBody)) => ApplyBlock (AlonzoEra c)
10 changes: 0 additions & 10 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Data.hs

This file was deleted.

63 changes: 8 additions & 55 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Genesis.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,17 +28,6 @@ module Cardano.Ledger.Alonzo.Genesis (
agMaxCollateralInputs
),
toAlonzoGenesisPairs,

-- * Deprecated
alonzoGenesisAesonPairs,
coinsPerUTxOWord,
costmdls,
prices,
maxTxExUnits,
maxBlockExUnits,
maxValSize,
collateralPercentage,
maxCollateralInputs,
)
where

Expand Down Expand Up @@ -196,48 +185,12 @@ instance ToJSON AlonzoGenesis where

toAlonzoGenesisPairs :: Aeson.KeyValue e a => AlonzoGenesis -> [a]
toAlonzoGenesisPairs ag =
[ "lovelacePerUTxOWord" .= coinsPerUTxOWord ag
, "costModels" .= costmdls ag
, "executionPrices" .= prices ag
, "maxTxExUnits" .= maxTxExUnits ag
, "maxBlockExUnits" .= maxBlockExUnits ag
, "maxValueSize" .= maxValSize ag
, "collateralPercentage" .= collateralPercentage ag
, "maxCollateralInputs" .= maxCollateralInputs ag
[ "lovelacePerUTxOWord" .= agCoinsPerUTxOWord ag
, "costModels" .= agCostModels ag
, "executionPrices" .= agPrices ag
, "maxTxExUnits" .= agMaxTxExUnits ag
, "maxBlockExUnits" .= agMaxBlockExUnits ag
, "maxValueSize" .= agMaxValSize ag
, "collateralPercentage" .= agCollateralPercentage ag
, "maxCollateralInputs" .= agMaxCollateralInputs ag
]

alonzoGenesisAesonPairs :: Aeson.KeyValue e a => AlonzoGenesis -> [a]
alonzoGenesisAesonPairs = toAlonzoGenesisPairs
{-# DEPRECATED alonzoGenesisAesonPairs "In favor of `toAlonzoGenesisPairs`" #-}

coinsPerUTxOWord :: AlonzoGenesis -> CoinPerWord
coinsPerUTxOWord = agCoinsPerUTxOWord
{-# DEPRECATED coinsPerUTxOWord "Use `agCoinsPerUTxOWord` instead" #-}

costmdls :: AlonzoGenesis -> CostModels
costmdls = agCostModels
{-# DEPRECATED costmdls "Use `agCostModels` instead" #-}

prices :: AlonzoGenesis -> Prices
prices = agPrices
{-# DEPRECATED prices "Use `agPrices` instead" #-}

maxTxExUnits :: AlonzoGenesis -> ExUnits
maxTxExUnits = agMaxTxExUnits
{-# DEPRECATED maxTxExUnits "Use `agMaxTxExUnits` instead" #-}

maxBlockExUnits :: AlonzoGenesis -> ExUnits
maxBlockExUnits = agMaxBlockExUnits
{-# DEPRECATED maxBlockExUnits "Use `agMaxBlockExUnits` instead" #-}

maxValSize :: AlonzoGenesis -> Natural
maxValSize = agMaxValSize
{-# DEPRECATED maxValSize "Use `agMaxValSize` instead" #-}

collateralPercentage :: AlonzoGenesis -> Natural
collateralPercentage = agCollateralPercentage
{-# DEPRECATED collateralPercentage "Use `agCollateralPercentage` instead" #-}

maxCollateralInputs :: AlonzoGenesis -> Natural
maxCollateralInputs = agMaxCollateralInputs
{-# DEPRECATED maxCollateralInputs "Use `agMaxCollateralInputs` instead" #-}
5 changes: 0 additions & 5 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Language.hs

This file was deleted.

20 changes: 4 additions & 16 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Plutus/Evaluate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ module Cardano.Ledger.Alonzo.Plutus.Evaluate (
evalPlutusScriptsWithLogs,
CollectError (..),
collectPlutusScriptsWithContext,
lookupPlutusScript,

-- * Execution units estimation
TransactionScriptFailure (..),
Expand All @@ -33,8 +32,7 @@ where

import Cardano.Ledger.Alonzo.Core
import Cardano.Ledger.Alonzo.Plutus.Context (ContextError, EraPlutusContext (..), LedgerTxInfo (..))
import Cardano.Ledger.Alonzo.Scripts (plutusScriptLanguage, toAsItem, toAsIx)
import qualified Cardano.Ledger.Alonzo.Scripts as Scripts
import Cardano.Ledger.Alonzo.Scripts (lookupPlutusScript, plutusScriptLanguage, toAsItem, toAsIx)
import Cardano.Ledger.Alonzo.TxWits (lookupRedeemer, unRedeemers)
import Cardano.Ledger.Alonzo.UTxO (AlonzoEraUTxO, AlonzoScriptsNeeded (..))
import Cardano.Ledger.BaseTypes (ProtVer (pvMajor), kindObject, natVersion, pvMajor)
Expand Down Expand Up @@ -140,16 +138,6 @@ instance
BadTranslation err ->
kindObject "BadTranslation" ["error" .= toJSON err]

-- | Given a script hash and a Map of available scripts, find the PlutusScript. Returns
-- Nothing when script is missing or it is not a PlutusScript
lookupPlutusScript ::
AlonzoEraScript era =>
Map.Map (ScriptHash (EraCrypto era)) (Script era) ->
ScriptHash (EraCrypto era) ->
Maybe (PlutusScript era)
lookupPlutusScript = flip Scripts.lookupPlutusScript
{-# DEPRECATED lookupPlutusScript "In favor of new version with arguments flipped: `Scripts.lookupPlutusScript`" #-}

collectPlutusScriptsWithContext ::
forall era.
( AlonzoEraTxBody era
Expand Down Expand Up @@ -188,7 +176,7 @@ collectPlutusScriptsWithContext epochInfo systemStart pp tx utxo =
ScriptsProvided scriptsProvided = getScriptsProvided utxo tx
AlonzoScriptsNeeded scriptsNeeded = getScriptsNeeded utxo (tx ^. bodyTxL)
neededPlutusScripts =
mapMaybe (\(sp, sh) -> (,) (sh, sp) <$> Scripts.lookupPlutusScript sh scriptsProvided) scriptsNeeded
mapMaybe (\(sp, sh) -> (,) (sh, sp) <$> lookupPlutusScript sh scriptsProvided) scriptsNeeded
usedLanguages = Set.fromList $ map (plutusScriptLanguage . snd) neededPlutusScripts

getScriptWithRedeemer ((plutusScriptHash, plutusPurpose), plutusScript) =
Expand Down Expand Up @@ -406,14 +394,14 @@ evalTxExUnitsWithLogs pp tx utxo epochInfo systemStart = Map.mapWithKey findAndC
Map.map
( \(sp, sh) ->
( hoistPlutusPurpose toAsItem sp
, Scripts.lookupPlutusScript sh scriptsProvided
, lookupPlutusScript sh scriptsProvided
, sh
)
)
purposeToScriptHash
plutusScript <-
note (MissingScript pointer ptrToPlutusScriptNoContext) $
Scripts.lookupPlutusScript plutusScriptHash scriptsProvided
lookupPlutusScript plutusScriptHash scriptsProvided
let lang = plutusScriptLanguage plutusScript
costModel <-
note (NoCostModelInLedgerState lang) $ Map.lookup lang costModels
Expand Down
5 changes: 2 additions & 3 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Rules/Bbody.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,6 @@ import Cardano.Ledger.Binary (DecCBOR (..), EncCBOR (..))
import Cardano.Ledger.Binary.Coders
import Cardano.Ledger.Block (Block (..))
import Cardano.Ledger.Core
import qualified Cardano.Ledger.Era as Era
import Cardano.Ledger.Keys (DSignable, Hash, coerceKeyRole)
import Cardano.Ledger.Shelley.BlockChain (incrBlocks)
import Cardano.Ledger.Shelley.LedgerState (LedgerState)
Expand Down Expand Up @@ -184,7 +183,7 @@ alonzoBbodyTransition ::
, Signal (EraRule "LEDGERS" era) ~ Seq (Tx era)
, EraSegWits era
, AlonzoEraTxWits era
, Era.TxSeq era ~ AlonzoTxSeq era
, TxSeq era ~ AlonzoTxSeq era
, Tx era ~ AlonzoTx era
, AlonzoEraPParams era
) =>
Expand Down Expand Up @@ -270,7 +269,7 @@ instance
, Signal (EraRule "LEDGERS" era) ~ Seq (AlonzoTx era)
, AlonzoEraTxWits era
, Tx era ~ AlonzoTx era
, Era.TxSeq era ~ AlonzoTxSeq era
, TxSeq era ~ AlonzoTxSeq era
, Tx era ~ AlonzoTx era
, EraSegWits era
, AlonzoEraPParams era
Expand Down
16 changes: 1 addition & 15 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Rules/Utxow.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,6 @@ module Cardano.Ledger.Alonzo.Rules.Utxow (
hasExactSetOfRedeemers,
missingRequiredDatums,
ppViewHashesMatch,
requiredSignersAreWitnessed,
)
where

Expand Down Expand Up @@ -79,7 +78,7 @@ import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Ledger.UTxO (EraUTxO (..), ScriptsProvided (..), UTxO (..))
import Control.DeepSeq (NFData)
import Control.Monad.Trans.Reader (asks)
import Control.SetAlgebra (domain, eval, (⊆), (➖))
import Control.SetAlgebra (domain, eval, (➖))
import Control.State.Transition.Extended
import Data.Foldable (sequenceA_)
import qualified Data.Map.Strict as Map
Expand Down Expand Up @@ -289,19 +288,6 @@ hasExactSetOfRedeemers tx (ScriptsProvided scriptsProvided) (AlonzoScriptsNeeded
, failureUnless (null missingRdmrs) (MissingRedeemers (map snd missingRdmrs))
]

-- ======================
requiredSignersAreWitnessed ::
AlonzoEraTxBody era =>
TxBody era ->
Set (KeyHash 'Witness (EraCrypto era)) ->
Test (AlonzoUtxowPredFailure era)
requiredSignersAreWitnessed txBody witsKeyHashes = do
let reqSignerHashes' = txBody ^. reqSignerHashesTxBodyL
failureUnless
(eval (reqSignerHashes' witsKeyHashes))
(MissingRequiredSigners (eval $ reqSignerHashes' witsKeyHashes))
{-# DEPRECATED requiredSignersAreWitnessed "As no longer used. `validateNeededWitnesses` now handles this check" #-}

-- =======================
{- scriptIntegrityHash txb = hashScriptIntegrity pp (languages txw) (txrdmrs txw) -}
ppViewHashesMatch ::
Expand Down
5 changes: 0 additions & 5 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Scripts/Data.hs

This file was deleted.

10 changes: 1 addition & 9 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Translation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ import Cardano.Ledger.Alonzo.Tx (AlonzoTx (..), IsValid (..))
import Cardano.Ledger.Binary (DecoderError)
import Cardano.Ledger.CertState (CommitteeState (..), PState (..), VState (..))
import Cardano.Ledger.Crypto (Crypto)
import Cardano.Ledger.Mary (MaryEra)
import Cardano.Ledger.Shelley.LedgerState (
CertState (..),
DState (..),
Expand Down Expand Up @@ -149,7 +148,7 @@ instance Crypto c => TranslateEra (AlonzoEra c) UTxOState where

instance Crypto c => TranslateEra (AlonzoEra c) UTxO where
translateEra _ctxt utxo =
return $ UTxO $ translateTxOut `Map.map` unUTxO utxo
return $ UTxO $ upgradeTxOut `Map.map` unUTxO utxo

instance Crypto c => TranslateEra (AlonzoEra c) ShelleyGovState where
translateEra ctxt ps =
Expand All @@ -165,10 +164,3 @@ instance Crypto c => TranslateEra (AlonzoEra c) ShelleyGovState where
instance Crypto c => TranslateEra (AlonzoEra c) ProposedPPUpdates where
translateEra _ctxt (ProposedPPUpdates ppup) =
return $ ProposedPPUpdates $ fmap (upgradePParamsUpdate def) ppup

translateTxOut ::
Crypto c =>
TxOut (MaryEra c) ->
TxOut (AlonzoEra c)
translateTxOut = upgradeTxOut
{-# DEPRECATED translateTxOut "Use `upgradeTxOut` instead" #-}
Loading

0 comments on commit 78b20b6

Please sign in to comment.