1
1
{-# LANGUAGE NumericUnderscores #-}
2
2
{-# LANGUAGE OverloadedStrings #-}
3
- {-# LANGUAGE TypeApplications #-}
4
3
5
4
module Test.Cardano.Db.Mock.Unit.Conway.Whitelist (
6
5
addTxMultiAssetsWhitelist ,
7
6
addTxMetadataWhitelist ,
8
7
addTxMetadataWhitelistMultiple ,
9
8
addSimpleTxStakeAddrsWhitelist ,
9
+ fullTxStakeAddressWhitelist ,
10
10
)
11
11
where
12
12
@@ -30,6 +30,7 @@ import qualified Test.Cardano.Db.Mock.UnifiedApi as UnifiedApi
30
30
import Test.Cardano.Db.Mock.Validate
31
31
import Test.Tasty.HUnit (Assertion ())
32
32
import Prelude (head , (!!) )
33
+ import Test.Cardano.Db.Mock.UnifiedApi (withConwayFindLeaderAndSubmit )
33
34
34
35
addTxMultiAssetsWhitelist :: IOManager -> [(Text , Text )] -> Assertion
35
36
addTxMultiAssetsWhitelist ioManager metadata = do
@@ -200,7 +201,7 @@ addTxMetadataWhitelistMultiple ioManager metadata = do
200
201
addSimpleTxStakeAddrsWhitelist :: IOManager -> [(Text , Text )] -> Assertion
201
202
addSimpleTxStakeAddrsWhitelist ioManager metadata = do
202
203
syncNodeConfig <- mksNodeConfig
203
- withCustomConfigAndLogs args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata
204
+ withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata
204
205
where
205
206
action = \ interpreter mockServer dbSync -> do
206
207
-- Forge a block
@@ -218,7 +219,6 @@ addSimpleTxStakeAddrsWhitelist ioManager metadata = do
218
219
testLabel = " conwayAddSimpleTx"
219
220
args = initCommandLineArgs {claFullMode = False }
220
221
cfgDir = conwayConfigDir
221
-
222
222
shelleyStakeAddrShortBs = toShort " e0921c25093b263793a1baf36166b819543f5822c62f72571111111111"
223
223
-- match all metadata keys of value 1
224
224
mksNodeConfig :: IO SyncNodeConfig
@@ -235,32 +235,44 @@ addSimpleTxStakeAddrsWhitelist ioManager metadata = do
235
235
}
236
236
}
237
237
238
- -- spendCollateralOutput :: IOManager -> [(Text, Text)] -> Assertion
239
- -- spendCollateralOutput =
240
- -- withFullConfig babbageConfigDir testLabel $ \interpreter mockServer dbSync -> do
241
- -- startDBSync dbSync
242
- -- void $ registerAllStakeCreds interpreter mockServer
243
-
244
- -- tx0 <-
245
- -- withBabbageLedgerState interpreter $
246
- -- Babbage.mkLockByScriptTx (UTxOIndex 0) [Babbage.TxOutNoInline False] 20000 20000
247
- -- void $ forgeNextFindLeaderAndSubmit interpreter mockServer [TxBabbage tx0]
248
238
249
- -- -- tx fails so its collateral output become actual output.
250
- -- let utxo0 = head (Babbage.mkUTxOBabbage tx0)
251
- -- tx1 <-
252
- -- withBabbageLedgerState interpreter $
253
- -- Babbage.mkUnlockScriptTxBabbage [UTxOInput (fst utxo0)] (UTxOIndex 1) (UTxOIndex 2) [UTxOPair utxo0] True False 10000 500
254
- -- void $ forgeNextFindLeaderAndSubmit interpreter mockServer [TxBabbage tx1]
255
- -- assertBlockNoBackoff dbSync 3
256
-
257
- -- let utxo1 = head (Babbage.mkUTxOCollBabbage tx1)
258
- -- tx2 <-
259
- -- withBabbageLedgerState interpreter $
260
- -- Babbage.mkUnlockScriptTxBabbage [UTxOPair utxo1] (UTxOIndex 3) (UTxOIndex 1) [UTxOPair utxo1] False True 10000 500
261
- -- void $ forgeNextFindLeaderAndSubmit interpreter mockServer [TxBabbage tx2]
239
+ fullTxStakeAddressWhitelist :: IOManager -> [(Text , Text )] -> Assertion
240
+ fullTxStakeAddressWhitelist ioManager metadata = do
241
+ syncNodeConfig <- mksNodeConfig
242
+ withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata
243
+ where
244
+ action =
245
+ \ interpreter mockServer dbSync -> do
246
+ startDBSync dbSync
247
+ -- Add some blocks with transactions
248
+ void $ withConwayFindLeaderAndSubmit interpreter mockServer $ \ state' ->
249
+ sequence
250
+ [ Conway. mkFullTx 0 100 state'
251
+ -- , Conway.mkFullTx 1 200 state'
252
+ ]
253
+ -- Wait for them to sync
254
+ assertBlockNoBackoff dbSync 1
255
+ assertTxCount dbSync 12
256
+ -- assertTxCount dbSync 13
262
257
263
- -- assertBlockNoBackoff dbSync 4
264
- -- assertBabbageCounts dbSync (1, 1, 1, 1, 2, 1, 1, 1, 1, 1, 1, 1, 1)
265
- -- where
266
- -- testLabel = "spendCollateralOutput"
258
+ testLabel = " fullTxStakeAddressWhitelist"
259
+ args = initCommandLineArgs {claFullMode = False }
260
+ cfgDir = conwayConfigDir
261
+ -- shelleyStakeAddr0 = toShort "e0addfa484e8095ff53f45b25cf337923cf79abe6ec192fdf288d621f9"
262
+ -- shelleyStakeAddr1 = toShort "e0921c25093b263793a1baf36166b819543f5822c62f72571111111111"
263
+ -- shelleyStakeAddr2 = toShort "e0921c25093b263793a1baf36166b819543f5822c62f72573333333333"
264
+ -- match all metadata keys of value 1
265
+ mksNodeConfig :: IO SyncNodeConfig
266
+ mksNodeConfig = do
267
+ initConfigFile <- mkSyncNodeConfig cfgDir args
268
+ let dncInsertOptions' = dncInsertOptions initConfigFile
269
+ pure $
270
+ initConfigFile
271
+ { dncInsertOptions =
272
+ dncInsertOptions'
273
+ { sioShelley =
274
+ ShelleyEnable
275
+ -- ShelleyStakeAddrs $
276
+ -- fromList [shelleyStakeAddr0, shelleyStakeAddr1, shelleyStakeAddr2]
277
+ }
278
+ }
0 commit comments