5
5
{-# LANGUAGE FlexibleInstances #-}
6
6
{-# LANGUAGE GADTs #-}
7
7
{-# LANGUAGE MultiParamTypeClasses #-}
8
+ {-# LANGUAGE OverloadedLists #-}
8
9
{-# LANGUAGE OverloadedStrings #-}
9
10
{-# LANGUAGE ScopedTypeVariables #-}
10
11
{-# LANGUAGE TypeApplications #-}
14
15
15
16
module Test.Cardano.Ledger.Examples.AlonzoAPI (tests ) where
16
17
17
- import Cardano.Ledger.Alonzo.Tx (alonzoMinFeeTx )
18
+ import Cardano.Ledger.Alonzo.Tx (alonzoMinFeeTx , hashData )
19
+ import Cardano.Ledger.Alonzo.TxWits (TxDats (.. ))
18
20
import Cardano.Ledger.BaseTypes (ProtVer (.. ), inject , natVersion )
19
21
import Cardano.Ledger.Coin (Coin (.. ))
22
+ import Cardano.Ledger.Conway.Core (AlonzoEraTxWits (.. ))
23
+ import Cardano.Ledger.Core (EraTx (.. ), EraTxWits (.. ), hashScript )
20
24
import Cardano.Ledger.Plutus (ExUnits (.. ))
21
25
import Cardano.Ledger.Plutus.Data (Data (.. ))
22
26
import Cardano.Ledger.Plutus.Language (Language (.. ))
23
27
import Cardano.Ledger.SafeHash (hashAnnotated )
24
28
import Cardano.Ledger.Tools (estimateMinFeeTx )
29
+ import Lens.Micro ((&) , (.~) )
25
30
import qualified PlutusLedgerApi.V1 as PV1
26
31
import Test.Cardano.Ledger.Core.KeyPair (mkWitnessVKey )
27
32
import Test.Cardano.Ledger.Examples.STSTestUtils (
@@ -34,9 +39,7 @@ import Test.Cardano.Ledger.Examples.STSTestUtils (
34
39
import Test.Cardano.Ledger.Generic.Fields (
35
40
PParamsField (.. ),
36
41
TxBodyField (.. ),
37
- TxField (.. ),
38
42
TxOutField (.. ),
39
- WitnessesField (.. ),
40
43
)
41
44
import Test.Cardano.Ledger.Generic.GenState (PlutusPurposeTag (.. ))
42
45
import Test.Cardano.Ledger.Generic.Proof
@@ -62,27 +65,16 @@ testEstimateMinFee =
62
65
where
63
66
pf = Alonzo
64
67
pparams = newPParams pf $ defaultPPs ++ [MinfeeA (Coin 1 )]
68
+ script = always 3 pf
69
+ dat = Data (PV1. I 123 )
65
70
validatingTxNoWits =
66
- newTx
67
- pf
68
- [ Body validatingBody
69
- , WitnessesI
70
- [ ScriptWits' [always 3 pf]
71
- , DataWits' [Data (PV1. I 123 )]
72
- , RdmrWits redeemers
73
- ]
74
- ]
71
+ mkBasicTx validatingBody
72
+ & witsTxL . scriptTxWitsL .~ [(hashScript script, script)]
73
+ & witsTxL . datsTxWitsL .~ TxDats [(hashData dat, dat)]
74
+ & witsTxL . rdmrsTxWitsL .~ redeemers
75
75
validatingTx =
76
- newTx
77
- pf
78
- [ Body validatingBody
79
- , WitnessesI
80
- [ AddrWits' [mkWitnessVKey (hashAnnotated validatingBody) (someKeys pf)]
81
- , ScriptWits' [always 3 pf]
82
- , DataWits' [Data (PV1. I 123 )]
83
- , RdmrWits redeemers
84
- ]
85
- ]
76
+ validatingTxNoWits
77
+ & witsTxL . addrTxWitsL .~ [mkWitnessVKey (hashAnnotated validatingBody) (someKeys pf)]
86
78
validatingBody =
87
79
newTxBody
88
80
pf
0 commit comments