Skip to content

Commit

Permalink
Extract txInAt utility function in core testlib Utils
Browse files Browse the repository at this point in the history
and use it to avoid duplication
  • Loading branch information
teodanciu committed Feb 1, 2024
1 parent b0bd81b commit f83e998
Show file tree
Hide file tree
Showing 5 changed files with 21 additions and 16 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import Cardano.Ledger.Plutus.Language (Language (..), plutusBinary)
import Cardano.Ledger.Shelley.Core
import Cardano.Ledger.Shelley.LedgerState
import Cardano.Ledger.Shelley.UTxO (getShelleyMinFeeTxUtxo)
import Cardano.Ledger.TxIn (TxIn (..), mkTxInPartial)
import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Ledger.UTxO (getMinFeeTxUtxo)
import Cardano.Ledger.Val
import Control.Monad (replicateM)
Expand All @@ -42,6 +42,7 @@ import Lens.Micro ((&), (.~), (^.))
import Test.Cardano.Ledger.Alonzo.Arbitrary (alwaysSucceeds)
import Test.Cardano.Ledger.Conway.ImpTest
import Test.Cardano.Ledger.Core.KeyPair (mkScriptAddr)
import Test.Cardano.Ledger.Core.Utils (txInAt)
import Test.Cardano.Ledger.Imp.Common

spec ::
Expand Down Expand Up @@ -105,7 +106,7 @@ spec = describe "UTxO" $ do
mkBasicTxBody
& outputsTxBodyL @era
.~ SSeq.fromList [mkBasicTxOut @era scriptAddr (inject (Coin 1000))]
pure $ txInAt 0 tx
pure $ txInAt (0 :: Int) tx

createRefScriptsUtxos :: [Script era] -> ImpTestM era (Map.Map (TxIn (EraCrypto era)) (Script era))
createRefScriptsUtxos scripts = do
Expand All @@ -121,7 +122,7 @@ spec = describe "UTxO" $ do
mkBasicTxBody
& outputsTxBodyL @era
.~ SSeq.fromList outs
let refIns = (\i -> txInAt (fromIntegral i) tx) <$> [0 .. length scripts - 1]
let refIns = (`txInAt` tx) <$> [0 .. length scripts - 1]
pure $ Map.fromList $ refIns `zip` scripts

spendScriptUsingRefScripts :: TxIn (EraCrypto era) -> Set.Set (TxIn (EraCrypto era)) -> ImpTestM era (Tx era)
Expand Down Expand Up @@ -152,8 +153,3 @@ spec = describe "UTxO" $ do
let refScriptFee = Coin 10
modifyPParams $ ppMinFeeRefScriptCoinsPerByteL .~ CoinPerByte refScriptFee
pure refScriptFee

txInAt :: Integer -> Tx era -> TxIn (EraCrypto era)
txInAt index tx =
let txid = txIdTx tx
in mkTxInPartial txid index
Original file line number Diff line number Diff line change
Expand Up @@ -9,12 +9,12 @@ import Cardano.Ledger.BaseTypes (inject)
import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Shelley.Core
import Cardano.Ledger.Shelley.UTxO (UTxO (..))
import Cardano.Ledger.TxIn (mkTxInPartial)
import qualified Data.Map.Strict as Map
import qualified Data.Sequence.Strict as SSeq
import qualified Data.Set as Set
import Lens.Micro ((&), (.~), (^.))
import Test.Cardano.Ledger.Core.KeyPair (mkAddr)
import Test.Cardano.Ledger.Core.Utils (txInAt)
import Test.Cardano.Ledger.Imp.Common
import Test.Cardano.Ledger.Shelley.ImpTest

Expand All @@ -36,7 +36,7 @@ spec = describe "LEDGER" $ do
.~ SSeq.singleton
(mkBasicTxOut (mkAddr (kpPayment1, kpStaking1)) $ inject coin1)
UTxO utxo1 <- getUTxO
case Map.lookup (mkTxInPartial (txIdTx tx1) 0) utxo1 of
case Map.lookup (txInAt (0 :: Int) tx1) utxo1 of
Just out1 -> out1 ^. coinTxOutL `shouldBe` coin1
Nothing -> expectationFailure "Could not find the TxOut of the first transaction"
kpPayment2 <- lookupKeyPair =<< freshKeyHash
Expand All @@ -47,12 +47,12 @@ spec = describe "LEDGER" $ do
mkBasicTxBody
& inputsTxBodyL
.~ Set.singleton
(mkTxInPartial (txIdTx tx1) 0)
(txInAt (0 :: Int) tx1)
& outputsTxBodyL @era
.~ SSeq.singleton
(mkBasicTxOut (mkAddr (kpPayment2, kpStaking2)) $ inject coin2)
UTxO utxo2 <- getUTxO
case Map.lookup (mkTxInPartial (txIdTx tx2) 0) utxo2 of
case Map.lookup (txInAt (0 :: Int) tx2) utxo2 of
Just out1 -> do
out1 ^. coinTxOutL `shouldBe` coin2
Nothing -> expectationFailure "Could not find the TxOut of the second transaction"
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ import Cardano.Ledger.Shelley.TxWits (
bootWits,
)
import Cardano.Ledger.Slot (SlotNo (..))
import Cardano.Ledger.TxIn (TxId (..), TxIn (..), mkTxInPartial)
import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Ledger.UTxO (UTxO (..))
import Cardano.Ledger.Val ((<->))
import Data.ByteString (ByteString)
Expand All @@ -70,6 +70,7 @@ import qualified Hedgehog.Range
import Lens.Micro
import qualified Test.Cardano.Chain.Common.Gen as Byron
import qualified Test.Cardano.Crypto.Gen as Byron
import Test.Cardano.Ledger.Core.Utils (txInAt)
import qualified Test.Cardano.Ledger.Shelley.ConcreteCryptoTypes as Original (C_Crypto)
import Test.Cardano.Ledger.Shelley.Generator.EraGen (genesisId)
import Test.Cardano.Ledger.Shelley.Generator.ShelleyEraGen ()
Expand Down Expand Up @@ -165,9 +166,8 @@ utxoState1 =
, utxosDonation = mempty
}
where
txid = TxId $ hashAnnotated txBody
bobResult = (mkTxInPartial txid 0, ShelleyTxOut bobAddr coinsToBob)
aliceResult = (mkTxInPartial txid 1, ShelleyTxOut aliceAddr (Coin 998990))
bobResult = (txInAt (0 :: Int) tx, ShelleyTxOut bobAddr coinsToBob)
aliceResult = (txInAt (1 :: Int) tx, ShelleyTxOut aliceAddr (Coin 998990))

utxoEnv :: UtxoEnv C
utxoEnv =
Expand Down
1 change: 1 addition & 0 deletions libs/cardano-ledger-core/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@

### `testlib`

* Add `txInAt`
* Add `mkScriptAddr`
* Deprecate `deserialiseRewardAcntOld` in favor of `deserialiseRewardAccountOld`
* Deprecate `mkVKeyRwdAcnt` in favor of `mkVKeyRewardAccount`
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module Test.Cardano.Ledger.Core.Utils (
epsilonMaybeEq,
testGlobals,
mkDummySafeHash,
txInAt,
)
where

Expand All @@ -15,8 +16,10 @@ import Cardano.Ledger.BaseTypes (
Network (..),
mkActiveSlotCoeff,
)
import Cardano.Ledger.Core
import Cardano.Ledger.Crypto (Crypto (..))
import Cardano.Ledger.SafeHash (SafeHash, unsafeMakeSafeHash)
import Cardano.Ledger.TxIn (TxIn, mkTxInPartial)
import Cardano.Slotting.EpochInfo (fixedEpochInfo)
import Cardano.Slotting.Time (SystemStart (..), mkSlotLength)
import Data.Data (Proxy)
Expand Down Expand Up @@ -64,3 +67,8 @@ testGlobals =

mkDummySafeHash :: forall c a. Crypto c => Proxy c -> Int -> SafeHash c a
mkDummySafeHash _ = unsafeMakeSafeHash . mkDummyHash @(HASH c)

txInAt :: (HasCallStack, Integral i, EraTx era) => i -> Tx era -> TxIn (EraCrypto era)
txInAt index tx =
let txid = txIdTx tx
in mkTxInPartial txid (toInteger index)

0 comments on commit f83e998

Please sign in to comment.