Skip to content

Commit

Permalink
Moved Slot, Credential, and Address to Cardano.Ledger
Browse files Browse the repository at this point in the history
Added deprecated versions of Slot, Credential, and Address which point to new versions
Changed all the imports to now refer to Cardano.Ledger. ormolised
  • Loading branch information
TimSheard committed Jun 10, 2021
1 parent 66df483 commit 2eaedff
Show file tree
Hide file tree
Showing 118 changed files with 1,777 additions and 990 deletions.
2 changes: 1 addition & 1 deletion alonzo/impl/src/Cardano/Ledger/Alonzo/PParams.hs
Expand Up @@ -86,6 +86,7 @@ import Cardano.Ledger.Serialization
ratioToCBOR,
rationalFromCBOR,
)
import Cardano.Ledger.Slot (EpochNo (..))
import Control.DeepSeq (NFData)
import Data.ByteString.Short (fromShort)
import Data.Coders
Expand Down Expand Up @@ -115,7 +116,6 @@ import Numeric.Natural (Natural)
import Shelley.Spec.Ledger.Orphans ()
import Shelley.Spec.Ledger.PParams (HKD, ProtVer (..))
import qualified Shelley.Spec.Ledger.PParams as Shelley (PParams' (..))
import Shelley.Spec.Ledger.Slot (EpochNo (..))

type PParamsUpdate era = PParams' StrictMaybe era

Expand Down
4 changes: 2 additions & 2 deletions alonzo/impl/src/Cardano/Ledger/Alonzo/PlutusScriptApi.hs
Expand Up @@ -23,6 +23,7 @@ module Cardano.Ledger.Alonzo.PlutusScriptApi
where

import Cardano.Binary (FromCBOR (..), ToCBOR (..))
import Cardano.Ledger.Address (Addr)
import Cardano.Ledger.Alonzo.Data (getPlutusData)
import Cardano.Ledger.Alonzo.Language (Language (..))
import Cardano.Ledger.Alonzo.Scripts (CostModel, ExUnits (..))
Expand All @@ -41,6 +42,7 @@ import Cardano.Ledger.Alonzo.TxInfo (runPLCScript, txInfo, valContext)
import Cardano.Ledger.Alonzo.TxWitness (TxWitness (txwitsVKey'), txscripts', unTxDats)
import Cardano.Ledger.BaseTypes (StrictMaybe (..))
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Credential (Credential (ScriptHashObj))
import qualified Cardano.Ledger.Crypto as CC (Crypto)
import Cardano.Ledger.Era (Crypto, Era, ValidateScript (..))
import Cardano.Ledger.Mary.Value (PolicyID (..))
Expand All @@ -59,8 +61,6 @@ import qualified Data.Set as Set
import GHC.Generics
import GHC.Records (HasField (..))
import NoThunks.Class (NoThunks)
import Shelley.Spec.Ledger.Address (Addr)
import Shelley.Spec.Ledger.Credential (Credential (ScriptHashObj))
import Shelley.Spec.Ledger.Delegation.Certificates (DCert (..))
import Shelley.Spec.Ledger.Scripts (ScriptHash (..))
import Shelley.Spec.Ledger.TxBody
Expand Down
2 changes: 1 addition & 1 deletion alonzo/impl/src/Cardano/Ledger/Alonzo/Rules/Bbody.hs
Expand Up @@ -29,6 +29,7 @@ import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Era (Era (Crypto), SupportsSegWit (..), TxInBlock)
import qualified Cardano.Ledger.Era as Era
import Cardano.Ledger.Keys (DSignable, Hash, coerceKeyRole)
import Cardano.Ledger.Slot (epochInfoEpoch, epochInfoFirst)
import Control.Monad.Trans.Reader (asks)
import Control.State.Transition
( Embed (..),
Expand Down Expand Up @@ -65,7 +66,6 @@ import Shelley.Spec.Ledger.STS.Bbody
BbodyState (..),
)
import Shelley.Spec.Ledger.STS.Ledgers (LedgersEnv (..))
import Shelley.Spec.Ledger.Slot (epochInfoEpoch, epochInfoFirst)
import Shelley.Spec.Ledger.TxBody (EraIndependentTxBody)

-- =======================================
Expand Down
16 changes: 8 additions & 8 deletions alonzo/impl/src/Cardano/Ledger/Alonzo/Rules/Utxo.hs
Expand Up @@ -16,6 +16,13 @@
module Cardano.Ledger.Alonzo.Rules.Utxo where

import Cardano.Binary (FromCBOR (..), ToCBOR (..), serialize)
import Cardano.Ledger.Address
( Addr (..),
RewardAcnt,
bootstrapAddressAttrsSize,
getNetwork,
getRwdNetwork,
)
import Cardano.Ledger.Alonzo.Data (dataHashSize)
import Cardano.Ledger.Alonzo.Rules.Utxos (UTXOS, UtxosPredicateFailure)
import Cardano.Ledger.Alonzo.Scripts (ExUnits (..), Prices, pointWiseExUnits)
Expand All @@ -38,6 +45,7 @@ import Cardano.Ledger.BaseTypes
)
import Cardano.Ledger.Coin
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Credential (Credential (..))
import Cardano.Ledger.Era (Crypto, Era, TxInBlock, ValidateScript (..))
import qualified Cardano.Ledger.Era as Era
import qualified Cardano.Ledger.Mary.Value as Alonzo (Value)
Expand Down Expand Up @@ -77,14 +85,6 @@ import GHC.Generics (Generic)
import GHC.Records
import NoThunks.Class (NoThunks)
import Numeric.Natural (Natural)
import Shelley.Spec.Ledger.Address
( Addr (..),
RewardAcnt,
bootstrapAddressAttrsSize,
getNetwork,
getRwdNetwork,
)
import Shelley.Spec.Ledger.Credential (Credential (..))
import qualified Shelley.Spec.Ledger.LedgerState as Shelley
import qualified Shelley.Spec.Ledger.STS.Utxo as Shelley
import Shelley.Spec.Ledger.Tx (TxIn)
Expand Down
4 changes: 2 additions & 2 deletions alonzo/impl/src/Cardano/Ledger/Alonzo/Rules/Utxow.hs
Expand Up @@ -14,6 +14,7 @@
module Cardano.Ledger.Alonzo.Rules.Utxow where

import Cardano.Binary (FromCBOR (..), ToCBOR (..))
import Cardano.Ledger.Address (Addr (..), bootstrapKeyHash, getRwdCred)
import Cardano.Ledger.Alonzo.Data (DataHash)
import Cardano.Ledger.Alonzo.Language (Language (..))
import Cardano.Ledger.Alonzo.PParams (PParams)
Expand All @@ -39,6 +40,7 @@ import Cardano.Ledger.BaseTypes
strictMaybeToMaybe,
)
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Credential (Credential (KeyHashObj))
import Cardano.Ledger.Era (Crypto, Era, SupportsSegWit (..), ValidateScript (..))
import Cardano.Ledger.Keys (GenDelegs, KeyHash, KeyRole (..), asWitness)
import Cardano.Ledger.Rules.ValidationMode ((?!#))
Expand All @@ -54,8 +56,6 @@ import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import GHC.Records
import NoThunks.Class
import Shelley.Spec.Ledger.Address (Addr (..), bootstrapKeyHash, getRwdCred)
import Shelley.Spec.Ledger.Credential (Credential (KeyHashObj))
import Shelley.Spec.Ledger.Delegation.Certificates
( delegCWitness,
genesisCWitness,
Expand Down
4 changes: 2 additions & 2 deletions alonzo/impl/src/Cardano/Ledger/Alonzo/Tx.hs
Expand Up @@ -75,6 +75,7 @@ import Cardano.Binary
serialize',
serializeEncoding,
)
import Cardano.Ledger.Address (Addr (..), RewardAcnt (..))
import Cardano.Ledger.Alonzo.Data (Data, DataHash, hashData)
import Cardano.Ledger.Alonzo.Language (Language (..), nonNativeLanguages)
import Cardano.Ledger.Alonzo.PParams (LangDepView (..), PParams, getLanguageView)
Expand Down Expand Up @@ -105,6 +106,7 @@ import Cardano.Ledger.Alonzo.TxWitness
import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Compactible
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Credential (Credential (ScriptHashObj))
import qualified Cardano.Ledger.Crypto as CC
import Cardano.Ledger.Era (Crypto, Era, ValidateScript (isNativeScript))
import Cardano.Ledger.Keys (KeyRole (Witness))
Expand Down Expand Up @@ -141,9 +143,7 @@ import GHC.Generics (Generic)
import GHC.Records (HasField (..))
import NoThunks.Class (NoThunks)
import Numeric.Natural (Natural)
import Shelley.Spec.Ledger.Address (Addr (..), RewardAcnt (..))
import Shelley.Spec.Ledger.Address.Bootstrap (BootstrapWitness)
import Shelley.Spec.Ledger.Credential (Credential (ScriptHashObj))
import Shelley.Spec.Ledger.Delegation.Certificates (DCert (..))
import Shelley.Spec.Ledger.Scripts (ScriptHash)
import Shelley.Spec.Ledger.TxBody (TxIn (..), Wdrl (..), WitVKey, unWdrl)
Expand Down
2 changes: 1 addition & 1 deletion alonzo/impl/src/Cardano/Ledger/Alonzo/TxBody.hs
Expand Up @@ -65,6 +65,7 @@ import Cardano.Binary
decodeListLenOrIndef,
encodeListLen,
)
import Cardano.Ledger.Address (Addr)
import Cardano.Ledger.Alonzo.Data (AuxiliaryDataHash (..), DataHash)
import Cardano.Ledger.BaseTypes
( Network,
Expand Down Expand Up @@ -126,7 +127,6 @@ import GHC.Generics (Generic)
import GHC.Records (HasField (..))
import GHC.Stack (HasCallStack)
import NoThunks.Class (InspectHeapNamed (..), NoThunks)
import Shelley.Spec.Ledger.Address (Addr)
import Shelley.Spec.Ledger.CompactAddr (CompactAddr, compactAddr, decompactAddr)
import Shelley.Spec.Ledger.Delegation.Certificates (DCert)
import Shelley.Spec.Ledger.PParams (Update)
Expand Down
4 changes: 2 additions & 2 deletions alonzo/impl/src/Cardano/Ledger/Alonzo/TxInfo.hs
Expand Up @@ -10,6 +10,7 @@ module Cardano.Ledger.Alonzo.TxInfo where
-- =============================================

import Cardano.Crypto.Hash.Class (Hash (UnsafeHash))
import Cardano.Ledger.Address (Addr (..), RewardAcnt (..))
import Cardano.Ledger.Alonzo.Data (Data (..), getPlutusData)
import Cardano.Ledger.Alonzo.Scripts (CostModel (..), ExUnits (..), Script (..))
import Cardano.Ledger.Alonzo.Tx
Expand All @@ -28,6 +29,7 @@ import Cardano.Ledger.Alonzo.TxWitness (TxWitness, unTxDats)
import Cardano.Ledger.BaseTypes (StrictMaybe (..))
import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Core as Core (TxBody, TxOut, Value)
import Cardano.Ledger.Credential (Credential (KeyHashObj, ScriptHashObj), Ptr (..), StakeReference (..))
import qualified Cardano.Ledger.Crypto as CC (Crypto)
import Cardano.Ledger.Era (Crypto, Era)
import Cardano.Ledger.Keys (KeyHash (..), hashKey)
Expand Down Expand Up @@ -83,8 +85,6 @@ import qualified Plutus.V1.Ledger.Value as P (CurrencySymbol (..), TokenName (..
import qualified PlutusCore.Evaluation.Machine.ExMemory as P (ExCPU (..), ExMemory (..))
import qualified PlutusTx as P (Data (..))
import qualified PlutusTx.IsData.Class as P (IsData (..))
import Shelley.Spec.Ledger.Address (Addr (..), RewardAcnt (..))
import Shelley.Spec.Ledger.Credential (Credential (KeyHashObj, ScriptHashObj), Ptr (..), StakeReference (..))
import Shelley.Spec.Ledger.Scripts (ScriptHash (..))
import Shelley.Spec.Ledger.TxBody
( DCert (..),
Expand Down
1 change: 0 additions & 1 deletion alonzo/test/cardano-ledger-alonzo-test.cabal
Expand Up @@ -52,7 +52,6 @@ library
flat,
hashable,
plutus-tx,
plutus-tx-plugin,
plutus-ledger-api,
QuickCheck,
shelley-spec-ledger-test,
Expand Down

0 comments on commit 2eaedff

Please sign in to comment.