Skip to content

Commit

Permalink
Implement MINT script tests
Browse files Browse the repository at this point in the history
  • Loading branch information
neilmayhew committed Nov 18, 2024
1 parent 149eec9 commit 26fab88
Show file tree
Hide file tree
Showing 6 changed files with 29 additions and 28 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ import Cardano.Ledger.Plutus (
)
import Control.Monad ((<=<))
import Lens.Micro ((&), (.~))
import Test.Cardano.Ledger.Alonzo.Arbitrary ()
import Test.Cardano.Ledger.Alonzo.ImpTest
import Test.Cardano.Ledger.Imp.Common
import Test.Cardano.Ledger.Plutus.Examples
Expand Down Expand Up @@ -81,10 +82,12 @@ spec = describe "Valid transactions" $ do
mkBasicTx $
mkBasicTxBody & withdrawalsTxBodyL .~ Withdrawals [(account, mempty)]

it "Validating MINT script" $ do
const $ pendingWith "not implemented yet"
it "Not validating MINT script" $ do
const $ pendingWith "not implemented yet"
it "Validating MINT script" $ do
expectTxSuccess <=< submitTx <=< mkTokenMintingTx $ alwaysSucceedsNoDatumHash

it "Not validating MINT script" $ do
expectTxSuccess <=< submitPhase2Invalid <=< mkTokenMintingTx $ alwaysFailsNoDatumHash

it "Validating scripts everywhere" $ do
const $ pendingWith "not implemented yet"
it "Acceptable supplimentary datum" $ do
Expand Down
1 change: 1 addition & 0 deletions eras/conway/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@

### `testlib`

* Remove `mintingTokenTx` (which is replaced by `mkTokenMintingTx` in Mary)
* Add `minFeeUpdateGovAction`
* Add `mkTreasuryWithdrawalsGovAction` and `mkParameterChangeGovAction`
* Switch to using `ImpSpec` package
Expand Down
1 change: 0 additions & 1 deletion eras/conway/impl/cardano-ledger-conway.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -163,7 +163,6 @@ library testlib
cardano-ledger-babbage:{cardano-ledger-babbage, testlib},
cardano-ledger-conway,
cardano-ledger-core:{cardano-ledger-core, testlib},
cardano-ledger-mary,
cardano-ledger-shelley:{cardano-ledger-shelley, testlib},
cardano-strict-containers,
containers,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -28,11 +28,6 @@ import Cardano.Ledger.Conway.TxInfo
import Cardano.Ledger.Credential (Credential (..), StakeReference (..))
import Cardano.Ledger.DRep
import Cardano.Ledger.Keys (KeyRole (..))
import Cardano.Ledger.Mary.Value (
MaryValue (..),
MultiAsset (..),
PolicyID (..),
)
import Cardano.Ledger.Plutus
import Cardano.Ledger.Shelley.LedgerState
import Cardano.Ledger.Shelley.Rules (ShelleyUtxowPredFailure (..))
Expand Down Expand Up @@ -597,11 +592,10 @@ costModelsSpec =
govIdConstitution1 <-
enactConstitution SNothing (Constitution anchor SNothing) dRep committeeMembers'

let mintingScriptHash = hashPlutusScript (evenRedeemerNoDatum SPlutusV3)
mintingTokenTx <- mkTokenMintingTx $ hashPlutusScript (evenRedeemerNoDatum SPlutusV3)

impAnn "Minting token fails" $ do
tx <- mintingTokenTx @era (mkBasicTx @era mkBasicTxBody) mintingScriptHash
submitFailingTx tx [injectFailure $ CollectErrors [NoCostModel PlutusV3]]
submitFailingTx mintingTokenTx [injectFailure $ CollectErrors [NoCostModel PlutusV3]]

govIdPPUpdate1 <-
enactCostModels
Expand All @@ -619,8 +613,7 @@ costModelsSpec =
committeeMembers'

impAnn "Minting token succeeds" $ do
tx <- mintingTokenTx @era (mkBasicTx @era mkBasicTxBody) mintingScriptHash
submitTx_ tx
submitTx_ mintingTokenTx

impAnn "Updating CostModels succeeds" $ do
void $
Expand Down Expand Up @@ -695,18 +688,6 @@ testPlutusV1V2Failure sh badField lenz errorField = do
CollectErrors [BadTranslation errorField]
)

mintingTokenTx :: ConwayEraImp era => Tx era -> ScriptHash (EraCrypto era) -> ImpTestM era (Tx era)
mintingTokenTx tx sh = do
name <- arbitrary
count <- choose (0, 10)
let policyId = PolicyID sh
let ma = MultiAsset $ Map.singleton policyId [(name, count)]
addr <- freshKeyAddr_
pure $
tx
& bodyTxL . mintTxBodyL .~ ma
& bodyTxL . outputsTxBodyL <>~ [mkBasicTxOut addr (MaryValue mempty ma)]

enactCostModels ::
ConwayEraImp era =>
StrictMaybe (GovPurposeId 'PParamUpdatePurpose era) ->
Expand Down
1 change: 1 addition & 0 deletions eras/mary/impl/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@

### `testlib`

* Add `mkTokenMintingTx`
* Switch to using `ImpSpec` package

## 1.7.0.1
Expand Down
18 changes: 17 additions & 1 deletion eras/mary/impl/testlib/Test/Cardano/Ledger/Mary/ImpTest.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
Expand All @@ -8,6 +9,7 @@
module Test.Cardano.Ledger.Mary.ImpTest (
MaryEraImp,
module Test.Cardano.Ledger.Allegra.ImpTest,
mkTokenMintingTx,
) where

import Cardano.Crypto.DSIGN (DSIGNAlgorithm (..), Ed25519DSIGN)
Expand All @@ -18,8 +20,10 @@ import Cardano.Ledger.Crypto (Crypto (..))
import Cardano.Ledger.Mary (MaryEra)
import Cardano.Ledger.Mary.Core
import Cardano.Ledger.Mary.Value
import Lens.Micro ((&), (.~))
import Test.Cardano.Ledger.Allegra.ImpTest
import Test.Cardano.Ledger.Common
import Test.Cardano.Ledger.Imp.Common
import Test.Cardano.Ledger.Mary.Arbitrary ()
import Test.Cardano.Ledger.Mary.TreeDiff ()

instance
Expand Down Expand Up @@ -52,3 +56,15 @@ instance
, Signable (DSIGN c) (Hash (HASH c) EraIndependentTxBody)
) =>
MaryEraImp (MaryEra c)

mkTokenMintingTx :: MaryEraImp era => ScriptHash (EraCrypto era) -> ImpTestM era (Tx era)
mkTokenMintingTx sh = do
name <- arbitrary
count <- choose (1, 10)
let policyId = PolicyID sh
let ma = multiAssetFromList [(policyId, name, count)]
addr <- freshKeyAddr_
pure $
mkBasicTx mkBasicTxBody
& bodyTxL . mintTxBodyL .~ ma
& bodyTxL . outputsTxBodyL .~ [mkBasicTxOut addr (MaryValue mempty ma)]

0 comments on commit 26fab88

Please sign in to comment.