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 16, 2021
1 parent 6474f68 commit 381a73c
Show file tree
Hide file tree
Showing 117 changed files with 990 additions and 1,024 deletions.
2 changes: 1 addition & 1 deletion alonzo/impl/src/Cardano/Ledger/Alonzo/PParams.hs
Original file line number Diff line number Diff line change
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
Original file line number Diff line number Diff line change
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
Original file line number Diff line number Diff line change
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
Original file line number Diff line number Diff line change
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
Original file line number Diff line number Diff line change
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
Original file line number Diff line number Diff line change
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
Original file line number Diff line number Diff line change
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
Original file line number Diff line number Diff line change
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
60 changes: 2 additions & 58 deletions alonzo/test/lib/Test/Cardano/Ledger/Alonzo/AlonzoEraGen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@
module Test.Cardano.Ledger.Alonzo.AlonzoEraGen where

import Cardano.Binary (ToCBOR (toCBOR), serializeEncoding')
import Cardano.Ledger.Address (Addr (..))
import Cardano.Ledger.Alonzo (AlonzoEra)
import Cardano.Ledger.Alonzo.Data as Alonzo (AuxiliaryData (..), Data (..), DataHash)
import Cardano.Ledger.Alonzo.Language (Language (PlutusV1))
Expand All @@ -36,6 +37,7 @@ import Cardano.Ledger.AuxiliaryData (AuxiliaryDataHash)
import Cardano.Ledger.BaseTypes (Network (..), StrictMaybe (..))
import Cardano.Ledger.Coin (Coin (..))
import qualified Cardano.Ledger.Core as Core (PParams, PParamsDelta, Script, TxOut)
import Cardano.Ledger.Credential (Credential (..))
import qualified Cardano.Ledger.Crypto as CC
import Cardano.Ledger.Era (Crypto, Era (..), ValidateScript (..))
import Cardano.Ledger.Hashes (ScriptHash)
Expand All @@ -62,8 +64,6 @@ import GHC.Records (HasField (..))
import Plutus.V1.Ledger.Api (defaultCostModelParams)
import qualified PlutusTx as P (Data (..))
import qualified PlutusTx as Plutus
import Shelley.Spec.Ledger.Address (Addr (..))
import Shelley.Spec.Ledger.Credential (Credential (..))
import Shelley.Spec.Ledger.PParams (Update)
import Shelley.Spec.Ledger.TxBody (DCert, TxIn, Wdrl)
import Shelley.Spec.Ledger.UTxO (UTxO (..))
Expand Down Expand Up @@ -414,59 +414,3 @@ someLeaf _proxy x =
in case mode of
0 -> TimelockScript $ (RequireAnyOf . Seq.fromList) [RequireTimeStart slot, RequireTimeExpire slot]
_ -> TimelockScript $ RequireSignature x

{-
The bytestring below is a compiled (and then converted to ShortByteString) version of
this PlutusScript. See the source Test.Cardano.Ledger.Alonzo.Examples
It has three arguments 1) the data 2) the redeemer, 3) the context. Designed to be used
as a script locking an output.
guessTheNumber3args' :: P.Data -> P.Data -> P.Data -> ()
guessTheNumber3args' d1 d2 _d3 = if d1 P.== d2 then () else (P.error ())
guessTheNumber3args :: ShortByteString
guessTheNumber3args =
toShort . toStrict . serialise . P.fromCompiledCode $
$$(P.compile [||guessTheNumber3args'||])
-}

{-
guessTheNumber3args:: ShortByteString
guessTheNumber3args = read "\SOH\NUL\NUL2\NUL2\NUL2\NUL32\NUL \STX\NUL3 \STX\NUL32\NUL \STX\NUL2\NUL2\NUL2\NUL2\NUL3 \STX\NUL333 \STX\NUL \STX\NUL \STX\NUL2\NUL2\NUL2\NUL2\NUL2\NUL2\NUL\NUL\DC2\NUL \STX\NUL350\NAK35\NULS\NULq \NUL\SOH\NUL0\STX \NUL\SUB \ETXP\ENQ\SOH\160\EM\DC2\NULa \NUL\SOH5\NUL\"\NUL \NUL\SOH5\NUL\DC2\NUL \NUL\STX5UP\SYN\DC2\NUL \STX\NUL3\NUL2\NUL \STX\NUL3350\a\NUL\"\NUL333S\NUL\128\STX \STX\NUL3\SOH0\ETX\NUL\"\NUL \STX\NUL\SOH\130\NUL \NUL\ETB \STX\NUL\SOHr\NUL \NUL\ETB\SOH\130\NUL \ETX3350\t\NUL2\NUL \NUL\CAN \STX\NUL \ETX3S\SOH\131\&0\DC4\NULP\ETX \ETX3S\SOHq \NUL\SOH0\v\DC2\NUL\NUL\DLE\ENQ\NUL2\NUL\SOH\160\FS \STX\NUL\SOH\130\NUL \NUL\CAN \STX\NUL\SOH\128\EM \ETX3350\b\NUL\"\NUL \NUL\ETB \STX\NUL \NUL\CAN \STX\NUL3\SOH \ETX\NUL\"\NUL \NUL\ETB \STX\NUL\SOHp\CAN \ETX3350\b\NUL\"\NUL \NUL\ETB \STX\NUL \NUL\CAN \STX\NUL\SOHr\NUL \ETX3S\SOHA \NUL\SOH0\b\DC2\NUL\NUL\DLE\ETX\NUL\"\NUL \NUL\ETB\SOH\130\NUL333S\NUL\128\STX \STX\NUL\SOHr\NUL \STX\NUL\SOH\130\NUL \NUL\ETB \STX\NUL\SOHr\NUL \ETX3S\SOHA \NUL\SOH\NULp\ETX\NUL \CAN \STX\NUL55P\f\NUL\"\NUL \ETXSU\NUL\224\ETX \STX\NUL350\SYN30\b\DC2\NUL\NUL\DLE\EOT\NUL\"\NUL30\t\DC2\NUL\NUL\DLE\EOT\NUL\"\NUL\SOH\128\SUB \SOH \STX\NUL \STX\NUL \ETX\NULP\ACK \STX\NUL\DC2\NUL \STX\NUL \STX\NUL3\NUL@\a\NULb\NUL\DC2\NUL \STX\NUL \STX\NUL0\ETX\NULb\NUL\DC2\NUL \STX\NUL \STX\NUL0\STX\NULb\NUL\DC2\NUL \STX\NUL \STX\NUL0\SOH\NULb\NUL\NUL\DC1\DC2\NUL \SOH \ETX0\SOH\NUL0\STX\DC1 \NUL\SOH \STX\NUL2\NUL35z\128\b\EOT\128A\155\164\NUL\128\EOT\128\b\NUL\200\NUL\204\213\234\NUL \DLE\NUL\230o\NUL\STX\NUL\DC3P\SOH \NUL\SOH\DC2\NUL0\SOH5P\n \STX\NUL\DC2\NUL \STX\NUL355\NUL\192\STX \ETX3SP\r\NUL\"\NUL\NUL\178\NUL \STX\NUL\NUL\192\f \STX\NUL \ETX3SP\SI\NULB\NUL\NUL\194\NUL \STX\NUL350\r3\NUL\144\ACK\NUL2\NUL350\f\DC2\NUL\NUL\DLE\n\NUL`\ETX \NUL\SI\SOH\DLE\SO\NUL\177 \STX\NUL\NUL! \STX\NUL\NUL\DC2\NUL\NUL\DC1 \NUL\SOH \NUL\SOH\DC1 \STX\NUL\NUL! \STX\NUL\DC2\NUL \ETX0\SOH\NUL@\ETX\DC2\NUL\NUL\DC1\DC2\NUL2\NUL0\SOH\NUL\DC2\NUL \ETX0\ETX2\NUL0\SOH\NUL\DLE\STX\NUL\DC1\DC1\DC2\NUL3P\STX \SOH \ETX0\SOH \ETXP\ETX \STX\NUL0\STX\NUL2\NUL5\NUL2\NUL \ETX\NUL\DLE\ETX\NUL\DC1 \ETX \ETX \ETX\NUL\DLE\SOH \STX\NUL3\NUL3 \ETX\NUL\DLE\SOH\NUL \SOH \STX\NUL\DC2\NUL50\EOT\DC2\NUL50\EOT\NUL3P\ETX\NUL\DLE\SOH\SOH"
-}

guess :: Alonzo.Script era
guess = guessTheNumber3

{-
guessTheNumber'3 :: P.Data -> P.Data -> P.Data -> ()
guessTheNumber'3 d1 d2 _d3 = if d1 P.== d2 then () else (P.error ())
guessTheNumber3 :: ShortByteString
guessTheNumber3 =
toShort . toStrict . serialise . P.fromCompiledCode $
$$(P.compile [||guessTheNumber'3||])
isEven3 :: [Word8]
isEven3 =
concat
[ [1, 0, 0, 51, 50, 0, 32, 2, 0, 50, 0, 50, 0, 51, 32],
[2, 0, 51, 50, 0, 32, 2, 0, 51, 51, 51, 32, 2, 0, 32],
[2, 0, 32, 2, 0, 51, 32, 2, 0, 50, 0, 50, 0, 0, 18],
[0, 32, 2, 0, 51, 51, 51, 83, 0, 112, 3, 32, 2, 0, 98],
[0, 32, 2, 0, 98, 0, 32, 3, 51, 83, 1, 99, 51, 80, 20],
[1, 83, 55, 144, 1, 36, 0, 137, 0, 1, 0, 0, 73, 0, 26],
[128, 56, 4, 128, 65, 0, 16, 3, 16, 1, 0, 48, 3, 9, 0],
[48, 144, 0, 0, 144, 0, 0, 144, 0, 144, 1, 0, 16, 1, 0],
[16, 1, 128, 40, 3, 16, 1, 0, 9, 0, 16, 1, 0, 16, 1],
[0, 25, 128, 32, 3, 128, 49, 0, 9, 0, 16, 1, 0, 16, 1],
[0, 24, 1, 128, 49, 0, 9, 0, 16, 1, 0, 16, 1, 0, 24],
[1, 0, 49, 0, 9, 0, 16, 1, 0, 16, 1, 0, 24, 0, 128],
[49, 0, 0, 8, 137, 0, 16, 0, 1, 9, 0, 16, 0, 144, 1],
[0, 25, 128, 8, 2, 0, 24, 144, 0, 0, 136, 144, 1, 0, 9],
[0, 25, 128, 8, 1, 128, 16, 137, 0, 0, 8, 144, 0, 0, 144],
[1, 0, 25, 0, 25, 154, 189, 64, 4, 1, 128, 20, 205, 210, 0],
[64, 2, 36, 0, 64, 0, 4, 36, 0, 64, 0, 2, 64, 0, 3]
]
-}
6 changes: 6 additions & 0 deletions cardano-ledger-core/cardano-ledger-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -40,28 +40,34 @@ library
hs-source-dirs: src

exposed-modules:
Cardano.Ledger.Address
Cardano.Ledger.AuxiliaryData
Cardano.Ledger.BaseTypes
Cardano.Ledger.Coin
Cardano.Ledger.Compactible
Cardano.Ledger.Core
Cardano.Ledger.Credential
Cardano.Ledger.Crypto
Cardano.Ledger.Era
Cardano.Ledger.Keys
Cardano.Ledger.Hashes
Cardano.Ledger.Rules.ValidationMode
Cardano.Ledger.SafeHash
Cardano.Ledger.Serialization
Cardano.Ledger.Slot
Cardano.Ledger.Tx
Cardano.Ledger.Val

build-depends:
aeson,
base16-bytestring,
binary,
bytestring,
cardano-binary,
cardano-crypto-class,
cardano-crypto-praos,
cardano-crypto-wrapper,
cardano-ledger-byron,
cardano-prelude,
cardano-slotting,
containers,
Expand Down
Loading

0 comments on commit 381a73c

Please sign in to comment.