Skip to content

Commit 1aea6f6

Browse files
committed
Fix consumed_by entries with a migration
1 parent 2545bb3 commit 1aea6f6

File tree

13 files changed

+147
-6
lines changed

13 files changed

+147
-6
lines changed

CHANGELOG.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,9 @@
11
# Revision history for cardano-db-sync
22

3+
## 13.4.1.0
4+
- Fix consumed_by option for Byron inputs. A migration fixes old wrong values in place. [#1821]
5+
- Fix only-utxo preset populating the metadata instead of the multiassets
6+
37
## 13.4.0.0
48

59
- Voting metadata parsing falls back to CIP-100 when CIP-108 or CIP-119 is not followed [#1779]

cardano-chain-gen/cardano-chain-gen.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
cabal-version: 3.6
22

33
name: cardano-chain-gen
4-
version: 13.4.0.0
4+
version: 13.4.1.0
55
synopsis: A fake chain generator for testing cardano DB sync.
66
description: A fake chain generator for testing cardano DB sync.
77
homepage: https://github.com/IntersectMBO/cardano-db-sync

cardano-db-sync/cardano-db-sync.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
cabal-version: 3.6
22

33
name: cardano-db-sync
4-
version: 13.4.0.0
4+
version: 13.4.1.0
55
synopsis: The Cardano DB Sync node
66
description: A Cardano node that follows the Cardano chain and inserts data from the
77
chain into a PostgresQL database.
@@ -119,6 +119,7 @@ library
119119

120120
Cardano.DbSync.Rollback
121121

122+
Cardano.DbSync.Fix.ConsumedBy
122123
Cardano.DbSync.Fix.EpochStake
123124
Cardano.DbSync.Fix.PlutusDataBytes
124125
Cardano.DbSync.Fix.PlutusScripts

cardano-db-sync/src/Cardano/DbSync/Api.hs

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Cardano.DbSync.Api (
1212
setConsistentLevel,
1313
getConsistentLevel,
1414
isConsistent,
15+
getIsConsumedFixed,
1516
noneFixed,
1617
isDataFixed,
1718
getIsSyncFixed,
@@ -52,6 +53,7 @@ import Cardano.BM.Trace (Trace, logInfo, logWarning)
5253
import qualified Cardano.Chain.Genesis as Byron
5354
import Cardano.Crypto.ProtocolMagic (ProtocolMagicId (..))
5455
import qualified Cardano.Db as DB
56+
import qualified Cardano.Db as Multiplex (queryWrongConsumedBy)
5557
import Cardano.DbSync.Api.Types
5658
import Cardano.DbSync.Cache.Types (CacheCapacity (..), newEmptyCache, useNoCache)
5759
import Cardano.DbSync.Config.Cardano
@@ -112,6 +114,15 @@ isConsistent env = do
112114
Consistent -> pure True
113115
_ -> pure False
114116

117+
getIsConsumedFixed :: SyncEnv -> IO (Maybe Word64)
118+
getIsConsumedFixed env =
119+
case (DB.pcmPruneTxOut pcm, DB.pcmConsumeOrPruneTxOut pcm) of
120+
(False, True) -> Just <$> DB.runDbIohkNoLogging backend Multiplex.queryWrongConsumedBy
121+
_ -> pure Nothing
122+
where
123+
pcm = soptPruneConsumeMigration $ envOptions env
124+
backend = envBackend env
125+
115126
noneFixed :: FixesRan -> Bool
116127
noneFixed NoneFixRan = True
117128
noneFixed _ = False

cardano-db-sync/src/Cardano/DbSync/Era/Byron/Insert.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@
88

99
module Cardano.DbSync.Era.Byron.Insert (
1010
insertByronBlock,
11+
resolveTxInputs,
1112
) where
1213

1314
import Cardano.BM.Trace (Trace, logDebug, logInfo)
Lines changed: 55 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,55 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
3+
module Cardano.DbSync.Fix.ConsumedBy (fixConsumedBy) where
4+
5+
import Cardano.BM.Trace (Trace, logWarning)
6+
import qualified Cardano.Chain.Block as Byron hiding (blockHash)
7+
import qualified Cardano.Chain.UTxO as Byron
8+
import qualified Cardano.Crypto as Crypto (serializeCborHash)
9+
import qualified Cardano.Db as DB
10+
import Cardano.DbSync.Era.Byron.Insert
11+
import Cardano.DbSync.Era.Byron.Util (blockPayload, unTxHash)
12+
import Cardano.DbSync.Era.Util
13+
import Cardano.DbSync.Error
14+
import Cardano.DbSync.Types
15+
import Cardano.Prelude hiding (length)
16+
import Database.Persist.SqlBackend.Internal
17+
import Ouroboros.Consensus.Byron.Ledger (ByronBlock (..))
18+
import Ouroboros.Consensus.Cardano.Block (HardForkBlock (..))
19+
20+
fixConsumedBy :: SqlBackend -> Trace IO Text -> Integer -> CardanoBlock -> IO (Integer, Bool)
21+
fixConsumedBy backend tracer lastSize cblk = case cblk of
22+
BlockByron blk -> (\(n, bl) -> (n + lastSize, bl)) <$> fixBlock backend tracer blk
23+
_ -> pure (lastSize, True)
24+
25+
fixBlock :: SqlBackend -> Trace IO Text -> ByronBlock -> IO (Integer, Bool)
26+
fixBlock backend tracer bblk = case byronBlockRaw bblk of
27+
Byron.ABOBBoundary _ -> pure (0, False)
28+
Byron.ABOBBlock blk -> do
29+
runReaderT (fix 0 (blockPayload blk)) backend
30+
where
31+
fix totalSize [] = pure (totalSize, False)
32+
fix totalSize (tx : txs) = do
33+
mn <- runExceptT $ fixTx tx
34+
case mn of
35+
Right n -> fix (totalSize + n) txs
36+
Left err -> do
37+
liftIO $
38+
logWarning tracer $
39+
mconcat
40+
[ "While fixing tx "
41+
, textShow tx
42+
, ", encountered error "
43+
, textShow err
44+
]
45+
pure (totalSize, True)
46+
47+
fixTx :: MonadIO m => Byron.TxAux -> ExceptT SyncNodeError (ReaderT SqlBackend m) Integer
48+
fixTx tx = do
49+
txId <- liftLookupFail "resolving tx" $ DB.queryTxId txHash
50+
resolvedInputs <- mapM resolveTxInputs (toList $ Byron.txInputs (Byron.taTx tx))
51+
lift $ DB.updateListTxOutConsumedByTxId (prepUpdate txId <$> resolvedInputs)
52+
pure $ fromIntegral $ length resolvedInputs
53+
where
54+
txHash = unTxHash $ Crypto.serializeCborHash (Byron.taTx tx)
55+
prepUpdate txId (_, _, txOutId, _) = (txOutId, txId)

cardano-db-sync/src/Cardano/DbSync/Sync.hs

Lines changed: 60 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,7 @@ import Cardano.DbSync.Api.Types (ConsistentLevel (..), FixesRan (..), LedgerEnv
3434
import Cardano.DbSync.Config
3535
import Cardano.DbSync.Database
3636
import Cardano.DbSync.DbAction
37+
import Cardano.DbSync.Fix.ConsumedBy
3738
import Cardano.DbSync.Fix.PlutusDataBytes
3839
import Cardano.DbSync.Fix.PlutusScripts
3940
import Cardano.DbSync.LocalStateQuery
@@ -209,6 +210,28 @@ dbSyncProtocols syncEnv metricsSetters tc codecConfig version bversion =
209210
backend = envBackend syncEnv
210211

211212
initAction channel = do
213+
consumedFixed <- getIsConsumedFixed syncEnv
214+
case consumedFixed of
215+
Nothing -> oldActionFixes channel
216+
Just wrongEntriesSize | wrongEntriesSize == 0 -> do
217+
logInfo tracer "Found no wrong entries"
218+
oldActionFixes channel
219+
Just wrongEntriesSize -> do
220+
logInfo tracer $
221+
mconcat ["Found ", textShow wrongEntriesSize, " consumed_by_tx_id wrong entries"]
222+
fixedEntries <-
223+
runPeer
224+
localChainSyncTracer
225+
(cChainSyncCodec codecs)
226+
channel
227+
( Client.chainSyncClientPeer $
228+
chainSyncClientFixConsumed backend tracer wrongEntriesSize
229+
)
230+
logInfo tracer $
231+
mconcat ["Fixed ", textShow fixedEntries, " consumed_by_tx_id wrong entries"]
232+
pure False
233+
234+
oldActionFixes channel = do
212235
fr <- getIsSyncFixed syncEnv
213236
let skipFix = soptSkipFix $ envOptions syncEnv
214237
let onlyFix = soptOnlyFix $ envOptions syncEnv
@@ -439,6 +462,43 @@ drainThePipe n0 client = go n0
439462
, recvMsgRollBackward = \_pt _tip -> pure $ go n'
440463
}
441464

465+
chainSyncClientFixConsumed ::
466+
SqlBackend -> Trace IO Text -> Word64 -> ChainSyncClient CardanoBlock (Point CardanoBlock) (Tip CardanoBlock) IO Integer
467+
chainSyncClientFixConsumed backend tracer wrongTotalSize = Client.ChainSyncClient $ do
468+
liftIO $ logInfo tracer "Starting chainsync to fix consumed_by_tx_id Byron entries. See issue https://github.com/IntersectMBO/cardano-db-sync/issues/1821. This makes resyncing unnecessary."
469+
pure $ Client.SendMsgFindIntersect [genesisPoint] clientStIntersect
470+
where
471+
clientStIntersect =
472+
Client.ClientStIntersect
473+
{ Client.recvMsgIntersectFound = \_blk _tip ->
474+
Client.ChainSyncClient $
475+
pure $
476+
Client.SendMsgRequestNext (pure ()) (clientStNext 0)
477+
, Client.recvMsgIntersectNotFound = \_tip ->
478+
panic "Failed to find intersection with genesis."
479+
}
480+
481+
clientStNext :: Integer -> Client.ClientStNext CardanoBlock (Point CardanoBlock) (Tip CardanoBlock) IO Integer
482+
clientStNext lastSize =
483+
Client.ClientStNext
484+
{ Client.recvMsgRollForward = \blk _tip -> Client.ChainSyncClient $ do
485+
(lastSize', ended) <- fixConsumedBy backend tracer lastSize blk
486+
logSize lastSize lastSize'
487+
if ended
488+
then pure $ Client.SendMsgDone lastSize'
489+
else pure $ Client.SendMsgRequestNext (pure ()) (clientStNext lastSize')
490+
, Client.recvMsgRollBackward = \_point _tip ->
491+
Client.ChainSyncClient $
492+
pure $
493+
Client.SendMsgRequestNext (pure ()) (clientStNext lastSize)
494+
}
495+
496+
logSize :: Integer -> Integer -> IO ()
497+
logSize lastSize newSize = do
498+
when (newSize `div` 200_000 > lastSize `div` 200_000) $
499+
logInfo tracer $
500+
mconcat ["Fixed ", textShow newSize, "/", textShow wrongTotalSize, " entries"]
501+
442502
chainSyncClientFixData ::
443503
SqlBackend -> Trace IO Text -> FixData -> ChainSyncClient CardanoBlock (Point CardanoBlock) (Tip CardanoBlock) IO ()
444504
chainSyncClientFixData backend tracer fixData = Client.ChainSyncClient $ do

cardano-db-tool/cardano-db-tool.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
cabal-version: 3.6
22

33
name: cardano-db-tool
4-
version: 13.4.0.0
4+
version: 13.4.1.0
55
synopsis: Utilities to manage the cardano-db-sync databases.
66
description: Utilities and executable, used to manage and validate the
77
PostgreSQL db and the ledger database of the cardano-db-sync node

cardano-db/cardano-db.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
cabal-version: 3.6
22

33
name: cardano-db
4-
version: 13.3.0.0
4+
version: 13.4.1.0
55
synopsis: A base PostgreSQL component for the cardano-db-sync node.
66
description: Code for the Cardano DB Sync node that is shared between the
77
cardano-db-node and other components.

cardano-db/src/Cardano/Db/Migration/Extra/CosnumedTxOut/Queries.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -141,6 +141,14 @@ _validateMigration trce = do
141141
]
142142
pure False
143143

144+
queryWrongConsumedBy :: MonadIO m => ReaderT SqlBackend m Word64
145+
queryWrongConsumedBy = do
146+
res <- select $ do
147+
txOut <- from $ table @TxOut
148+
where_ (just (txOut ^. TxOutTxId) E.==. txOut ^. TxOutConsumedByTxId)
149+
pure countRows
150+
pure $ maybe 0 unValue (listToMaybe res)
151+
144152
--------------------------------------------------------------------------------------------------
145153
-- Inserts
146154
--------------------------------------------------------------------------------------------------

0 commit comments

Comments
 (0)