@@ -8,21 +8,26 @@ module Test.Cardano.Db.Mock.Unit.Conway.Tx (
88 addTxMetadata ,
99 addTxMetadataDisabled ,
1010 addTxMetadataWhitelist ,
11+ addTxMetadataWhitelistMultiple ,
1112) where
1213
14+ import Cardano.DbSync.Config (SyncNodeConfig (.. ))
15+ import Cardano.DbSync.Config.Types (MetadataConfig (.. ), SyncInsertOptions (.. ))
1316import Cardano.Ledger.Shelley.TxAuxData (Metadatum (.. ))
1417import Cardano.Mock.ChainSync.Server (IOManager ())
1518import qualified Cardano.Mock.Forging.Tx.Conway as Conway
1619import qualified Cardano.Mock.Forging.Tx.Shelley as Shelley
1720import Cardano.Mock.Forging.Types (UTxOIndex (.. ))
1821import Cardano.Mock.Query (queryNullTxDepositExists , queryTxMetadataCount )
1922import Cardano.Prelude hiding (head )
23+ import Data.List.NonEmpty (fromList )
2024import qualified Data.Map as Map
2125import Test.Cardano.Db.Mock.Config
2226import qualified Test.Cardano.Db.Mock.UnifiedApi as UnifiedApi
2327import Test.Cardano.Db.Mock.Validate
2428import Test.Tasty.HUnit (Assertion ())
2529import Prelude (head )
30+ import Cardano.Api.Ledger (Coin (.. ))
2631
2732addSimpleTx :: IOManager -> [(Text , Text )] -> Assertion
2833addSimpleTx =
@@ -98,75 +103,151 @@ consumeSameBlock =
98103 testLabel = " conwayConsumeSameBlock"
99104
100105addTxMetadata :: IOManager -> [(Text , Text )] -> Assertion
101- addTxMetadata = do
102- withCustomConfigAndDropDB args Nothing cfgDir testLabel $ \ interpreter mockServer dbSync -> do
103- startDBSync dbSync
104-
105- -- Add blocks with transactions
106- void $
107- UnifiedApi. withConwayFindLeaderAndSubmitTx interpreter mockServer $ \ _ ->
108- let txBody = Conway. mkDummyTxBody
109- auxData = Map. fromList [(1 , I 1 ), (2 , I 2 )]
110- in Right (Conway. mkAuxDataTx True txBody auxData)
111-
112- -- Wait for it to sync
113- assertBlockNoBackoff dbSync 1
114- -- Should have tx metadata
115- assertEqBackoff dbSync queryTxMetadataCount 2 [] " Expected tx metadata"
106+ addTxMetadata ioManager metadata = do
107+ syncNodeConfig <- mksNodeConfig
108+ withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata
116109 where
117- args =
118- initCommandLineArgs
119- { claFullMode = False
120- }
110+ action = \ interpreter mockServer dbSync -> do
111+ startDBSync dbSync
112+ -- Add blocks with transactions
113+ void $
114+ UnifiedApi. withConwayFindLeaderAndSubmitTx interpreter mockServer $ \ _ ->
115+ let txBody = Conway. mkDummyTxBody
116+ auxData = Map. fromList [(1 , I 1 ), (2 , I 2 )]
117+ in Right (Conway. mkAuxDataTx True txBody auxData)
118+
119+ -- Wait for it to sync
120+ assertBlockNoBackoff dbSync 1
121+ -- Should have tx metadata
122+ assertEqBackoff dbSync queryTxMetadataCount 2 [] " Expected tx metadata"
123+
124+ args = initCommandLineArgs {claFullMode = False }
121125 testLabel = " conwayConfigMetadataEnabled"
126+
122127 cfgDir = conwayConfigDir
123128
124- addTxMetadataWhitelist :: IOManager -> [(Text , Text )] -> Assertion
125- addTxMetadataWhitelist = do
126- withCustomConfigAndDropDB args Nothing cfgDir testLabel $ \ interpreter mockServer dbSync -> do
127- startDBSync dbSync
129+ mksNodeConfig :: IO SyncNodeConfig
130+ mksNodeConfig = do
131+ initConfigFile <- mkSyncNodeConfig cfgDir args
132+ let dncInsertOptions' = dncInsertOptions initConfigFile
133+ pure $
134+ initConfigFile
135+ { dncInsertOptions = dncInsertOptions' {sioMetadata = MetadataEnable }
136+ }
128137
129- -- Add blocks with transactions
130- void $ do
131- UnifiedApi. withConwayFindLeaderAndSubmitTx interpreter mockServer $ \ _ ->
132- let txBody = Conway. mkDummyTxBody
133- auxData = Map. fromList [(1 , I 1 ), (2 , I 2 )]
134- in Right (Conway. mkAuxDataTx True txBody auxData)
135138
136- -- Wait for it to sync
137- assertBlockNoBackoff dbSync 1
138- -- Should have tx metadata
139- assertEqBackoff dbSync queryTxMetadataCount 1 [] " Expected tx metadata"
139+ addTxMetadataDisabled :: IOManager -> [( Text , Text )] -> Assertion
140+ addTxMetadataDisabled ioManager metadata = do
141+ syncNodeConfig <- mksNodeConfig
142+ withCustomConfigAndDropDB args ( Just syncNodeConfig) cfgDir testLabel action ioManager metadata
140143 where
141- args =
142- initCommandLineArgs
143- { claConfigFilename = " test-db-sync-config-keep-metadata.json"
144- , claFullMode = False
145- }
146- testLabel = " conwayConfigMetadataKeep"
144+ action = \ interpreter mockServer dbSync -> do
145+ startDBSync dbSync
146+ -- Add blocks with transactions
147+ void $
148+ UnifiedApi. withConwayFindLeaderAndSubmitTx interpreter mockServer $ \ _ ->
149+ let txBody = Conway. mkDummyTxBody
150+ auxData = Map. fromList [(1 , I 1 ), (2 , I 2 )]
151+ in Right (Conway. mkAuxDataTx True txBody auxData)
152+
153+ -- Wait for it to sync
154+ assertBlockNoBackoff dbSync 1
155+ -- Should have tx metadata
156+ assertEqBackoff dbSync queryTxMetadataCount 0 [] " Expected tx metadata"
157+
158+ args = initCommandLineArgs {claFullMode = False }
159+ testLabel = " conwayConfigMetadataDisabled"
160+
147161 cfgDir = conwayConfigDir
148162
149- addTxMetadataDisabled :: IOManager -> [(Text , Text )] -> Assertion
150- addTxMetadataDisabled = do
151- withCustomConfigAndDropDB args Nothing cfgDir testLabel $ \ interpreter mockServer dbSync -> do
152- startDBSync dbSync
163+ mksNodeConfig :: IO SyncNodeConfig
164+ mksNodeConfig = do
165+ initConfigFile <- mkSyncNodeConfig cfgDir args
166+ let dncInsertOptions' = dncInsertOptions initConfigFile
167+ pure $
168+ initConfigFile
169+ { dncInsertOptions = dncInsertOptions' {sioMetadata = MetadataDisable }
170+ }
171+
172+ -- 2 blocks each with 4 metadata entries.
173+ -- The whitelist has one tx metadata key which is in the first block
174+ -- so only the TX in the first block should have tx metadata kept.
175+ addTxMetadataWhitelist :: IOManager -> [(Text , Text )] -> Assertion
176+ addTxMetadataWhitelist ioManager metadata = do
177+ syncNodeConfig <- mksNodeConfig
178+ withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata
179+ where
180+ action = \ interpreter mockServer dbSync -> do
181+ startDBSync dbSync
182+ -- Add transactions with metadata
183+ void $ do
184+ UnifiedApi. withConwayFindLeaderAndSubmitTx interpreter mockServer $ \ _ ->
185+ let txBody = Conway. mkDummyTxBodyWithCoin $ Coin 1_000
186+ auxData = Map. fromList [(1 , I 1 ), (2 , I 2 ), (3 , I 3 ), (4 , I 4 )]
187+ in Right (Conway. mkAuxDataTx True txBody auxData)
188+ void $ do
189+ UnifiedApi. withConwayFindLeaderAndSubmitTx interpreter mockServer $ \ _ ->
190+ let txBody = Conway. mkDummyTxBodyWithCoin $ Coin 2_000
191+ auxData = Map. fromList [(5 , I 5 ), (6 , I 6 ), (7 , I 7 ), (8 , I 8 )]
192+ in Right (Conway. mkAuxDataTx True txBody auxData)
193+
194+ assertBlockNoBackoff dbSync 2
195+ -- Should have first block's tx metadata
196+ assertEqBackoff dbSync queryTxMetadataCount 4 [] " Expected tx metadata"
197+
198+ args = initCommandLineArgs {claFullMode = False }
199+ testLabel = " conwayConfigMetadataWhitelist"
153200
154- -- Add blocks with transactions
155- void $
156- UnifiedApi. withConwayFindLeaderAndSubmitTx interpreter mockServer $ \ _ ->
157- let txBody = Conway. mkDummyTxBody
158- auxData = Map. singleton 1 (I 1 )
159- in Right (Conway. mkAuxDataTx True txBody auxData)
201+ cfgDir = conwayConfigDir
160202
161- -- Wait for it to sync
162- assertBlockNoBackoff dbSync 1
163- -- Should have tx metadata
164- assertEqBackoff dbSync queryTxMetadataCount 0 [] " Expected tx metadata"
203+ -- match all metadata keys of value 1
204+ mksNodeConfig :: IO SyncNodeConfig
205+ mksNodeConfig = do
206+ initConfigFile <- mkSyncNodeConfig cfgDir args
207+ let dncInsertOptions' = dncInsertOptions initConfigFile
208+ pure $
209+ initConfigFile
210+ { dncInsertOptions = dncInsertOptions' {sioMetadata = MetadataKeys $ fromList [1 ]}
211+ }
212+
213+ -- 2 blocks each with 4 metadata entries
214+ -- The whitelist is set to keys [1,6] each key in in different TX
215+ -- so all TxMetadata should be kept from both blocks.
216+ addTxMetadataWhitelistMultiple :: IOManager -> [(Text , Text )] -> Assertion
217+ addTxMetadataWhitelistMultiple ioManager metadata = do
218+ syncNodeConfig <- mksNodeConfig
219+ withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata
165220 where
166- args =
167- initCommandLineArgs
168- { claConfigFilename = " test-db-sync-config-no-metadata.json"
169- , claFullMode = False
170- }
171- testLabel = " conwayConfigMetadataDisabled"
221+ action = \ interpreter mockServer dbSync -> do
222+ startDBSync dbSync
223+ -- Add transactions with metadata
224+ void $ do
225+ UnifiedApi. withConwayFindLeaderAndSubmitTx interpreter mockServer $ \ _ ->
226+ let txBody = Conway. mkDummyTxBodyWithCoin $ Coin 1_000
227+ auxData = Map. fromList [(1 , I 1 ), (2 , I 2 ), (3 , I 3 ), (4 , I 4 )]
228+ in Right (Conway. mkAuxDataTx True txBody auxData)
229+ void $ do
230+ UnifiedApi. withConwayFindLeaderAndSubmitTx interpreter mockServer $ \ _ ->
231+ let txBody = Conway. mkDummyTxBodyWithCoin $ Coin 2_000
232+ auxData = Map. fromList [(5 , I 5 ), (6 , I 6 ), (7 , I 7 ), (8 , I 8 )]
233+ in Right (Conway. mkAuxDataTx True txBody auxData)
234+
235+ assertBlockNoBackoff dbSync 2
236+ -- Should have both block's tx metadata
237+ assertEqBackoff dbSync queryTxMetadataCount 8 [] " Expected tx metadata"
238+
239+ args = initCommandLineArgs {claFullMode = False }
240+ testLabel = " conwayConfigMetadataWhitelist"
241+
172242 cfgDir = conwayConfigDir
243+
244+ -- match all metadata keys of value 1
245+ mksNodeConfig :: IO SyncNodeConfig
246+ mksNodeConfig = do
247+ initConfigFile <- mkSyncNodeConfig cfgDir args
248+ let dncInsertOptions' = dncInsertOptions initConfigFile
249+ pure $
250+ initConfigFile
251+ { dncInsertOptions = dncInsertOptions' {sioMetadata = MetadataKeys $ fromList [1 ,6 ]}
252+ }
253+
0 commit comments