7
7
{-# LANGUAGE RankNTypes #-}
8
8
{-# LANGUAGE ScopedTypeVariables #-}
9
9
{-# LANGUAGE TypeFamilies #-}
10
+ {-# LANGUAGE TupleSections #-}
10
11
{-# LANGUAGE NoImplicitPrelude #-}
11
12
12
13
module Cardano.DbSync.Era.Shelley.Insert (
@@ -139,8 +140,12 @@ insertShelleyBlock syncEnv shouldLog withinTwoMins withinHalfHour blk details is
139
140
}
140
141
141
142
let zippedTx = zip [0 .. ] (Generic. blkTxs blk)
142
- let txInserter = insertTx syncEnv isMember blkId (sdEpochNo details) (Generic. blkSlotNo blk) applyResult
143
- blockGroupedData <- foldM (\ gp (idx, tx) -> txInserter idx tx gp) mempty zippedTx
143
+
144
+ txsPrepared <- foldAndAccM (prepareTx syncEnv blkId applyResult) zippedTx
145
+ txIds <- lift $ DB. insertManyTx (ptrTxDb <$> txsPrepared)
146
+ let txInserter = insertTx syncEnv blkId isMember (sdEpochNo details) (Generic. blkSlotNo blk) applyResult
147
+ let newZip = zipWith3 (\ tx txId ptr -> (txId, tx, ptr)) (Generic. blkTxs blk) txIds txsPrepared
148
+ blockGroupedData <- foldM txInserter mempty newZip
144
149
minIds <- insertBlockGroupedData syncEnv blockGroupedData
145
150
146
151
-- now that we've inserted the Block and all it's txs lets cache what we'll need
@@ -258,52 +263,44 @@ insertOnNewEpoch tracer iopts blkId slotNo epochNo newEpoch = do
258
263
259
264
-- -----------------------------------------------------------------------------
260
265
261
- insertTx ::
266
+ data PrepareTxRes = PrepareTxRes
267
+ { ptrTxDb :: DB. Tx
268
+ , ptrFees :: Word64
269
+ , ptrOutSum :: Word64
270
+ , ptrResolvedTxIn :: [(Generic. TxIn , Maybe DB. TxId , Either Generic. TxIn DB. TxOutId )]
271
+ }
272
+
273
+ prepareTx ::
262
274
(MonadBaseControl IO m , MonadIO m ) =>
263
275
SyncEnv ->
264
- IsPoolMember ->
265
276
DB. BlockId ->
266
- EpochNo ->
267
- SlotNo ->
268
277
ApplyResult ->
269
- Word64 ->
270
- Generic. Tx ->
271
- BlockGroupedData ->
272
- ExceptT SyncNodeError (ReaderT SqlBackend m ) BlockGroupedData
273
- insertTx syncEnv isMember blkId epochNo slotNo applyResult blockIndex tx grouped = do
278
+ [(ByteString , Generic. TxOut )] ->
279
+ (Word64 , Generic. Tx ) ->
280
+ ExceptT SyncNodeError (ReaderT SqlBackend m ) (PrepareTxRes , [(ByteString , Generic. TxOut )])
281
+ prepareTx syncEnv blkId applyResult blockTxOuts (blockIndex, tx) = do
274
282
let ! txHash = Generic. txHash tx
275
283
let ! mdeposits = if not (Generic. txValidContract tx) then Just (Coin 0 ) else lookupDepositsMap txHash (apDepositsMap applyResult)
276
284
let ! outSum = fromIntegral $ unCoin $ Generic. txOutSum tx
277
- ! withdrawalSum = fromIntegral $ unCoin $ Generic. txWithdrawalSum tx
278
285
hasConsumed = getHasConsumedOrPruneTxOut syncEnv
279
286
disInOut <- liftIO $ getDisableInOutState syncEnv
280
287
-- In some txs and with specific configuration we may be able to find necessary data within the tx body.
281
288
-- In these cases we can avoid expensive queries.
282
- (resolvedInputs, fees', deposits) <- case (disInOut, mdeposits, unCoin <$> Generic. txFees tx) of
283
- (True , _, _) -> pure ([] , 0 , unCoin <$> mdeposits)
284
- (_, Just deposits, Just fees) -> do
285
- (resolvedInputs, _) <- splitLast <$> mapM (resolveTxInputs hasConsumed False (fst <$> groupedTxOut grouped)) (Generic. txInputs tx)
286
- pure (resolvedInputs, fees, Just (unCoin deposits))
287
- (_, Nothing , Just fees) -> do
288
- (resolvedInputs, amounts) <- splitLast <$> mapM (resolveTxInputs hasConsumed False (fst <$> groupedTxOut grouped)) (Generic. txInputs tx)
289
- if any isNothing amounts
290
- then pure (resolvedInputs, fees, Nothing )
291
- else
292
- let ! inSum = sum $ map unDbLovelace $ catMaybes amounts
293
- in pure (resolvedInputs, fees, Just $ fromIntegral (inSum + withdrawalSum) - fromIntegral outSum - fromIntegral fees)
294
- (_, _, Nothing ) -> do
289
+ (resolvedInputs, fees', deposits) <- case (disInOut, unCoin <$> Generic. txFees tx) of
290
+ (True , _) -> pure ([] , 0 , unCoin <$> mdeposits)
291
+ (_, Just fees) -> do
292
+ resolvedInputsDB <- lift $ mapM (resolveTxInputs hasConsumed) (Generic. txInputs tx)
293
+ pure (resolvedInputsDB, fees, unCoin <$> mdeposits)
294
+ (_, Nothing ) -> do
295
295
-- Nothing in fees means a phase 2 failure
296
- (resolvedInsFull, amounts) <- splitLast <$> mapM (resolveTxInputs hasConsumed True ( fst <$> groupedTxOut grouped) ) (Generic. txInputs tx)
296
+ (resolvedInsFull, amounts) <- splitLast <$> mapM (resolveTxInputsValue blockTxOuts ) (Generic. txInputs tx)
297
297
let ! inSum = sum $ map unDbLovelace $ catMaybes amounts
298
298
! diffSum = if inSum >= outSum then inSum - outSum else 0
299
299
! fees = maybe diffSum (fromIntegral . unCoin) (Generic. txFees tx)
300
300
pure (resolvedInsFull, fromIntegral fees, Just 0 )
301
301
let fees = fromIntegral fees'
302
302
-- Insert transaction and get txId from the DB.
303
- ! txId <-
304
- lift
305
- . DB. insertTx
306
- $ DB. Tx
303
+ let txDb = DB. Tx
307
304
{ DB. txHash = txHash
308
305
, DB. txBlockId = blkId
309
306
, DB. txBlockIndex = blockIndex
@@ -316,15 +313,30 @@ insertTx syncEnv isMember blkId epochNo slotNo applyResult blockIndex tx grouped
316
313
, DB. txValidContract = Generic. txValidContract tx
317
314
, DB. txScriptSize = sum $ Generic. txScriptSizes tx
318
315
}
316
+ pure (PrepareTxRes txDb fees outSum resolvedInputs, blockTxOuts <> ((txHash,) <$> Generic. txOutputs tx))
319
317
318
+ insertTx ::
319
+ (MonadBaseControl IO m , MonadIO m ) =>
320
+ SyncEnv ->
321
+ DB. BlockId ->
322
+ IsPoolMember ->
323
+ EpochNo ->
324
+ SlotNo ->
325
+ ApplyResult ->
326
+ BlockGroupedData ->
327
+ (DB. TxId , Generic. Tx , PrepareTxRes ) ->
328
+ ExceptT SyncNodeError (ReaderT SqlBackend m ) BlockGroupedData
329
+ insertTx syncEnv blkId isMember epochNo slotNo applyResult grouped (txId, tx, ptr) = do
330
+ let ! txHash = Generic. txHash tx
331
+ disInOut <- liftIO $ getDisableInOutState syncEnv
320
332
if not (Generic. txValidContract tx)
321
333
then do
322
334
! txOutsGrouped <- mapM (prepareTxOut tracer cache iopts (txId, txHash)) (Generic. txOutputs tx)
323
335
324
- let ! txIns = map (prepareTxIn txId Map. empty) resolvedInputs
336
+ ! txIns <- mapM (prepareTxIn txId ( fst <$> groupedTxOut grouped) Map. empty) (ptrResolvedTxIn ptr)
325
337
-- There is a custom semigroup instance for BlockGroupedData which uses addition for the values `fees` and `outSum`.
326
338
-- Same happens bellow on last line of this function.
327
- pure (grouped <> BlockGroupedData txIns txOutsGrouped [] [] fees outSum )
339
+ pure (grouped <> BlockGroupedData txIns txOutsGrouped [] [] (ptrFees ptr) (ptrOutSum ptr) )
328
340
else do
329
341
-- The following operations only happen if the script passes stage 2 validation (or the tx has
330
342
-- no script).
@@ -378,8 +390,8 @@ insertTx syncEnv isMember blkId epochNo slotNo applyResult blockIndex tx grouped
378
390
mapM_ (insertGovActionProposal cache blkId txId (getGovExpiresAt applyResult epochNo)) $ zip [0 .. ] (Generic. txProposalProcedure tx)
379
391
mapM_ (insertVotingProcedures tracer cache txId) (Generic. txVotingProcedure tx)
380
392
381
- let ! txIns = map (prepareTxIn txId redeemers) resolvedInputs
382
- pure (grouped <> BlockGroupedData txIns txOutsGrouped txMetadata maTxMint fees outSum )
393
+ ! txIns <- mapM (prepareTxIn txId ( fst <$> groupedTxOut grouped) redeemers) (ptrResolvedTxIn ptr)
394
+ pure (grouped <> BlockGroupedData txIns txOutsGrouped txMetadata maTxMint (ptrFees ptr) (ptrOutSum ptr) )
383
395
where
384
396
tracer = getTrace syncEnv
385
397
cache = envCache syncEnv
@@ -467,23 +479,31 @@ insertCollateralTxOut tracer cache iopts (txId, _txHash) (Generic.TxOut index ad
467
479
hasScript = maybe False Generic. hasCredScript (Generic. getPaymentCred addr)
468
480
469
481
prepareTxIn ::
482
+ Monad m =>
470
483
DB. TxId ->
484
+ [ExtendedTxOut ] ->
471
485
Map Word64 DB. RedeemerId ->
472
- (Generic. TxIn , DB. TxId , Either Generic. TxIn DB. TxOutId ) ->
473
- ExtendedTxIn
474
- prepareTxIn txInId redeemers (txIn, txOutId, mTxOutId) =
475
- ExtendedTxIn
476
- { etiTxIn = txInDB
477
- , etiTxOutId = mTxOutId
478
- }
479
- where
480
- txInDB =
481
- DB. TxIn
482
- { DB. txInTxInId = txInId
483
- , DB. txInTxOutId = txOutId
484
- , DB. txInTxOutIndex = fromIntegral $ Generic. txInIndex txIn
485
- , DB. txInRedeemerId = mlookup (Generic. txInRedeemerIndex txIn) redeemers
486
- }
486
+ (Generic. TxIn , Maybe DB. TxId , Either Generic. TxIn DB. TxOutId ) ->
487
+ ExceptT SyncNodeError m ExtendedTxIn
488
+ prepareTxIn txInId groupedOutputs redeemers (txIn, mtxOutId, mTxOutId) = do
489
+ txOutId <- liftLookupFail " resolveScriptHash" $
490
+ case mtxOutId of
491
+ Just txOutId -> pure $ Right txOutId
492
+ Nothing -> case resolveInMemory txIn groupedOutputs of
493
+ Nothing -> pure $ Left $ DB. DbLookupTxHash (Generic. txInHash txIn)
494
+ Just txOut -> pure $ Right $ DB. txOutTxId $ etoTxOut txOut
495
+ let txInDB =
496
+ DB. TxIn
497
+ { DB. txInTxInId = txInId
498
+ , DB. txInTxOutId = txOutId
499
+ , DB. txInTxOutIndex = fromIntegral $ Generic. txInIndex txIn
500
+ , DB. txInRedeemerId = mlookup (Generic. txInRedeemerIndex txIn) redeemers
501
+ }
502
+ pure
503
+ ExtendedTxIn
504
+ { etiTxIn = txInDB
505
+ , etiTxOutId = mTxOutId
506
+ }
487
507
488
508
insertCollateralTxIn ::
489
509
(MonadBaseControl IO m , MonadIO m ) =>
0 commit comments