11{-# LANGUAGE DisambiguateRecordFields #-}
2- {-# LANGUAGE LambdaCase #-}
32{-# LANGUAGE NamedFieldPuns #-}
43{-# LANGUAGE NumericUnderscores #-}
54{-# LANGUAGE OverloadedStrings #-}
65{-# LANGUAGE ScopedTypeVariables #-}
7- {-# LANGUAGE TypeApplications #-}
86
97module Cardano.Testnet.Test.Cli.Transaction
108 ( hprop_transaction
119 ) where
1210
1311import Cardano.Api
1412import qualified Cardano.Api.Ledger as L
15- import qualified Cardano.Api.Ledger.Lens as A
1613import Cardano.Api.Shelley
1714
1815import qualified Cardano.Ledger.Core as L
@@ -22,19 +19,20 @@ import Prelude
2219
2320import Control.Monad (void )
2421import Data.Default.Class
25- import qualified Data.List as List
26- import qualified Data.Map as Map
2722import qualified Data.Text as Text
23+ import GHC.Exts (IsList (.. ))
2824import Lens.Micro
2925import System.FilePath ((</>) )
3026import qualified System.Info as SYS
3127
3228import Testnet.Components.Configuration
29+ import Testnet.Components.Query (findLargestUtxoWithAddress , findUtxosWithAddress ,
30+ getEpochStateView , waitForBlocks )
3331import Testnet.Process.Run (execCli' , mkExecConfig )
34- import Testnet.Property.Util (decodeEraUTxO , integrationRetryWorkspace )
32+ import Testnet.Property.Util (integrationRetryWorkspace )
3533import Testnet.Types
3634
37- import Hedgehog (Property )
35+ import Hedgehog (Property , (===) )
3836import qualified Hedgehog as H
3937import qualified Hedgehog.Extras.Test.Base as H
4038import qualified Hedgehog.Extras.Test.File as H
@@ -59,14 +57,16 @@ hprop_transaction = integrationRetryWorkspace 2 "simple transaction build" $ \te
5957 options = def { cardanoNodeEra = AnyShelleyBasedEra sbe }
6058
6159 TestnetRuntime
62- { testnetMagic
60+ { configurationFile
61+ , testnetMagic
6362 , testnetNodes
6463 , wallets= wallet0: _
6564 } <- cardanoTestnetDefault options def conf
6665
6766 poolNode1 <- H. headM testnetNodes
6867 poolSprocket1 <- H. noteShow $ nodeSprocket poolNode1
6968 execConfig <- mkExecConfig tempBaseAbsPath poolSprocket1 testnetMagic
69+ epochStateView <- getEpochStateView configurationFile (nodeSocketPath poolNode1)
7070
7171
7272 txbodyFp <- H. note $ work </> " tx.body"
@@ -79,22 +79,15 @@ hprop_transaction = integrationRetryWorkspace 2 "simple transaction build" $ \te
7979 , " --out-file" , work </> " pparams.json"
8080 ]
8181
82- void $ execCli' execConfig
83- [ anyEraToString cEra, " query" , " utxo"
84- , " --address" , Text. unpack $ paymentKeyInfoAddr wallet0
85- , " --cardano-mode"
86- , " --out-file" , work </> " utxo-1.json"
87- ]
88-
89- utxo1Json <- H. leftFailM . H. readJsonFile $ work </> " utxo-1.json"
90- UTxO utxo1 <- H. noteShowM $ decodeEraUTxO sbe utxo1Json
91- txin1 <- H. noteShow =<< H. headM (Map. keys utxo1)
82+ (txin1, TxOut _addr outValue _datum _refScript) <- H. nothingFailM $ findLargestUtxoWithAddress epochStateView sbe (paymentKeyInfoAddr wallet0)
83+ let (L. Coin initialAmount) = txOutValueToLovelace outValue
9284
85+ let transferAmount = 5_000_001
9386 void $ execCli' execConfig
9487 [ anyEraToString cEra, " transaction" , " build"
9588 , " --change-address" , Text. unpack $ paymentKeyInfoAddr wallet0
9689 , " --tx-in" , Text. unpack $ renderTxIn txin1
97- , " --tx-out" , Text. unpack (paymentKeyInfoAddr wallet0) <> " +" <> show @ Int 5_000_001
90+ , " --tx-out" , Text. unpack (paymentKeyInfoAddr wallet0) <> " +" <> show transferAmount
9891 , " --out-file" , txbodyFp
9992 ]
10093 cddlUnwitnessedTx <- H. readJsonFileOk txbodyFp
@@ -106,7 +99,7 @@ hprop_transaction = integrationRetryWorkspace 2 "simple transaction build" $ \te
10699 -- changed regarding fee calculation.
107100 -- 8.10 changed fee from 228 -> 330
108101 -- 9.2 changed fee from 330 -> 336
109- 336 H. === txFee
102+ 336 === txFee
110103
111104 void $ execCli' execConfig
112105 [ anyEraToString cEra, " transaction" , " sign"
@@ -120,28 +113,17 @@ hprop_transaction = integrationRetryWorkspace 2 "simple transaction build" $ \te
120113 , " --tx-file" , txbodySignedFp
121114 ]
122115
116+ H. noteShowM_ $ waitForBlocks epochStateView 1
123117
124118 H. byDurationM 1 15 " Expected UTxO found" $ do
125- void $ execCli' execConfig
126- [ anyEraToString cEra, " query" , " utxo"
127- , " --address" , Text. unpack $ paymentKeyInfoAddr wallet0
128- , " --cardano-mode"
129- , " --out-file" , work </> " utxo-2.json"
130- ]
131-
132- utxo2Json <- H. leftFailM . H. readJsonFile $ work </> " utxo-2.json"
133- UTxO utxo2 <- H. noteShowM $ decodeEraUTxO sbe utxo2Json
134- txouts2 <- H. noteShow $ L. unCoin . txOutValueLovelace . txOutValue . snd <$> Map. toList utxo2
135- H. assert $ 15_000_003_000_000 `List.elem` txouts2
119+ utxo2 <- findUtxosWithAddress epochStateView sbe (paymentKeyInfoAddr wallet0)
120+ txouts2 <- H. noteShow $ L. unCoin . txOutValueToLovelace . txOutValue . snd <$> toList utxo2
121+ H. assertWith txouts2 $ \ txouts2' ->
122+ [transferAmount, initialAmount - transferAmount - txFee] == txouts2'
136123
137124txOutValue :: TxOut ctx era -> TxOutValue era
138125txOutValue (TxOut _ v _ _) = v
139126
140- txOutValueLovelace :: TxOutValue era -> L. Coin
141- txOutValueLovelace = \ case
142- TxOutValueShelleyBased sbe v -> v ^. A. adaAssetL sbe
143- TxOutValueByron v -> v
144-
145127extractTxFee :: Tx era -> L. Coin
146128extractTxFee (ShelleyTx sbe ledgerTx) =
147129 shelleyBasedEraConstraints sbe $ ledgerTx ^. (L. bodyTxL . L. feeTxBodyL)
0 commit comments