Skip to content

Commit 018a0bf

Browse files
committed
fixes
1 parent 1143664 commit 018a0bf

File tree

8 files changed

+108
-32
lines changed

8 files changed

+108
-32
lines changed

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -187,7 +187,6 @@ library
187187
, lifted-base
188188
, memory
189189
, microlens
190-
-- , monad-control
191190
, network-mux
192191
, ouroboros-consensus
193192
, ouroboros-consensus-cardano

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

Lines changed: 9 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -246,24 +246,21 @@ runSyncNode metricsSetters trce iomgr dbConnSetting runNearTipMigrationFnc syncN
246246
-- communication channel between datalayer thread and chainsync-client thread
247247
threadChannels <- liftIO newThreadChannels
248248
liftIO $
249-
race_
250-
-- We split the main thread into two parts to allow for graceful shutdown of the main App db thread.
251-
(runDbThread syncEnv threadChannels)
252-
( mapConcurrently_
253-
id
254-
[ runSyncNodeClient metricsSetters syncEnv iomgr trce threadChannels (enpSocketPath syncNodeParams)
255-
, runFetchOffChainPoolThread syncEnv syncNodeConfigFromFile
256-
, runFetchOffChainVoteThread syncEnv syncNodeConfigFromFile
257-
, runLedgerStateWriteThread (getTrace syncEnv) (envLedgerEnv syncEnv)
258-
]
259-
)
249+
mapConcurrently_
250+
id
251+
[ runDbThread syncEnv threadChannels
252+
, runSyncNodeClient metricsSetters syncEnv iomgr trce threadChannels (enpSocketPath syncNodeParams)
253+
, runFetchOffChainPoolThread syncEnv syncNodeConfigFromFile
254+
, runFetchOffChainVoteThread syncEnv syncNodeConfigFromFile
255+
, runLedgerStateWriteThread (getTrace syncEnv) (envLedgerEnv syncEnv)
256+
]
260257
)
261258
where
262259
useShelleyInit :: SyncNodeConfig -> Bool
263260
useShelleyInit cfg =
264261
case dncShelleyHardFork cfg of
265262
CardanoTriggerHardForkAtEpoch (EpochNo 0) -> True
266-
_other -> False
263+
_ -> False
267264

268265
removeJsonbFromSchemaConfig = ioRemoveJsonbFromSchema $ soptInsertOptions syncOptions
269266
maybeLedgerDir = enpMaybeLedgerStateDir syncNodeParams

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -213,7 +213,7 @@ generateNewEpochEvents env details = do
213213
Strict.Just oldEpoch
214214
| currentEpochNo == EpochNo (1 + unEpochNo oldEpoch) ->
215215
Just $ LedgerNewEpoch currentEpochNo (getSyncStatus details)
216-
_otherwise -> Nothing
216+
_ -> Nothing
217217

218218
newCurrentEpochNo :: CurrentEpochNo
219219
newCurrentEpochNo =
@@ -456,7 +456,7 @@ verifySnapshotPoint env snapPoints =
456456
let valid = find (\(_, h) -> lsfHash lsf == hashToAnnotation h) hashes
457457
case valid of
458458
Just (slot, hash) | slot == lsfSlotNo lsf -> pure $ convertToDiskPoint slot hash
459-
_otherwise -> pure Nothing
459+
_ -> pure Nothing
460460
validLedgerFileToPoint (InMemory pnt) = do
461461
case pnt of
462462
GenesisPoint -> pure Nothing
@@ -465,7 +465,7 @@ verifySnapshotPoint env snapPoints =
465465
let valid = find (\(_, dbHash) -> getHeaderHash hsh == dbHash) hashes
466466
case valid of
467467
Just (dbSlotNo, _) | slotNo == dbSlotNo -> pure $ Just (pnt, True)
468-
_otherwise -> pure Nothing
468+
_ -> pure Nothing
469469

470470
convertToDiskPoint :: SlotNo -> ByteString -> Maybe (CardanoPoint, Bool)
471471
convertToDiskPoint slot hashBlob = (,False) <$> convertToPoint slot hashBlob

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

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ import Cardano.Ledger.Core (Value)
1616
import Cardano.Ledger.Mary.Value
1717
import Cardano.Ledger.Shelley.LedgerState
1818
import Cardano.Ledger.TxIn
19-
import Cardano.Prelude (ExceptT, lift, textShow, throwIO)
19+
import Cardano.Prelude (ExceptT, lift, textShow)
2020
import Control.Concurrent.Class.MonadSTM.Strict (atomically, readTVarIO, writeTVar)
2121
import Control.Monad.Extra
2222
import Control.Monad.IO.Class (liftIO)
@@ -34,12 +34,13 @@ import qualified Cardano.Db as DB
3434
import Cardano.DbSync.Api
3535
import Cardano.DbSync.Api.Types
3636
import Cardano.DbSync.Cache (queryTxIdWithCache)
37+
import Cardano.DbSync.DbEvent (liftDbLookupEither)
3738
import Cardano.DbSync.Era.Shelley.Generic.Tx.Babbage (fromTxOut)
3839
import Cardano.DbSync.Era.Shelley.Generic.Tx.Types (DBPlutusScript)
3940
import qualified Cardano.DbSync.Era.Shelley.Generic.Util as Generic
4041
import Cardano.DbSync.Era.Universal.Insert.Grouped
4142
import Cardano.DbSync.Era.Universal.Insert.Tx (insertTxOut)
42-
import Cardano.DbSync.Error (SyncNodeError)
43+
import Cardano.DbSync.Error (SyncNodeError, mkSyncNodeCallStack)
4344
import Cardano.DbSync.Ledger.State
4445
import Cardano.DbSync.Types
4546
import Cardano.DbSync.Util (maxBulkSize)
@@ -150,10 +151,7 @@ prepareTxOut ::
150151
prepareTxOut syncEnv (TxIn txIntxId (TxIx index), txOut) = do
151152
let txHashByteString = Generic.safeHashToByteString $ unTxId txIntxId
152153
let genTxOut = fromTxOut (fromIntegral index) txOut
153-
eTxId <- queryTxIdWithCache syncEnv txIntxId
154-
txId <- case eTxId of
155-
Left err -> liftIO $ throwIO err
156-
Right tid -> pure tid
154+
txId <- liftDbLookupEither mkSyncNodeCallStack $ queryTxIdWithCache syncEnv txIntxId
157155
insertTxOut syncEnv iopts (txId, txHashByteString) genTxOut
158156
where
159157
iopts = soptInsertOptions $ envOptions syncEnv

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

Lines changed: 7 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ import Cardano.DbSync.Cache.Epoch (rollbackMapEpochInCache)
5151
import qualified Cardano.DbSync.Cache.FIFO as FIFO
5252
import qualified Cardano.DbSync.Cache.LRU as LRU
5353
import Cardano.DbSync.Cache.Types (CacheAction (..), CacheInternal (..), CacheStatistics (..), CacheStatus (..), StakeCache (..), shouldCache)
54-
import Cardano.DbSync.DbEvent (liftDbLookup)
54+
import Cardano.DbSync.DbEvent (liftDbLookup, liftDbLookupMaybe)
5555
import qualified Cardano.DbSync.Era.Shelley.Generic.Util as Generic
5656
import Cardano.DbSync.Era.Shelley.Query
5757
import Cardano.DbSync.Error (SyncNodeError (..), mkSyncNodeCallStack)
@@ -218,14 +218,11 @@ queryPoolKeyWithCache ::
218218
SyncEnv ->
219219
CacheAction ->
220220
PoolKeyHash ->
221-
ExceptT SyncNodeError DB.DbM (Either DB.DbSessionError DB.PoolHashId)
221+
ExceptT SyncNodeError DB.DbM (Either DB.DbLookupError DB.PoolHashId)
222222
queryPoolKeyWithCache syncEnv cacheUA hsh =
223223
case envCache syncEnv of
224224
NoCache -> do
225-
mPhId <- lift $ DB.queryPoolHashId (Generic.unKeyHashRaw hsh)
226-
case mPhId of
227-
Nothing -> pure $ Left $ DB.DbSessionError DB.mkDbCallStack "queryPoolKeyWithCache: NoCache queryPoolHashId"
228-
Just phId -> pure $ Right phId
225+
liftDbLookupMaybe DB.mkDbCallStack "NoCache queryPoolHashId" $ DB.queryPoolHashId (Generic.unKeyHashRaw hsh)
229226
ActiveCache ci -> do
230227
mp <- liftIO $ readTVarIO (cPools ci)
231228
case Map.lookup hsh mp of
@@ -240,10 +237,10 @@ queryPoolKeyWithCache syncEnv cacheUA hsh =
240237
pure $ Right phId
241238
Nothing -> do
242239
liftIO $ missPools syncEnv
243-
mPhId <- lift $ DB.queryPoolHashId (Generic.unKeyHashRaw hsh)
244-
case mPhId of
245-
Nothing -> pure $ Left $ DB.DbSessionError DB.mkDbCallStack "queryPoolKeyWithCache: ActiveCache queryPoolHashId"
246-
Just phId -> do
240+
ePhId <- liftDbLookupMaybe DB.mkDbCallStack "ActiveCache queryPoolHashId" $ DB.queryPoolHashId (Generic.unKeyHashRaw hsh)
241+
case ePhId of
242+
Left err -> pure $ Left err
243+
Right phId -> do
247244
-- missed so we can't evict even with 'EvictAndReturn'
248245
when (shouldCache cacheUA) $
249246
liftIO $

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

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module Cardano.DbSync.DbEvent (
77
ThreadChannels (..),
88
liftDbSession,
99
liftDbLookup,
10+
liftDbLookupMaybe,
1011
liftDbSessionEither,
1112
liftDbLookupEither,
1213
liftSessionIO,
@@ -217,6 +218,17 @@ liftDbLookupEither cs mResult = do
217218
Left dbErr -> throwError $ SNErrDbLookupError cs dbErr
218219
Right val -> pure val
219220

221+
-- | Lift a Maybe-returning database operation to Either DbLookupError
222+
--
223+
-- Converts DbM (Maybe a) to ExceptT SyncNodeError DB.DbM (Either DB.DbLookupError a).
224+
-- Common pattern for database lookups that may not find results.
225+
liftDbLookupMaybe :: DB.DbCallStack -> Text -> DB.DbM (Maybe a) -> ExceptT SyncNodeError DB.DbM (Either DB.DbLookupError a)
226+
liftDbLookupMaybe cs errMsg dbAction = do
227+
result <- lift dbAction
228+
pure $ case result of
229+
Nothing -> Left $ DB.DbLookupError cs errMsg
230+
Just value -> Right value
231+
220232
liftSessionIO :: SyncNodeCallStack -> ExceptT DB.DbSessionError IO a -> ExceptT SyncNodeError IO a
221233
liftSessionIO cs dbAction = do
222234
result <- liftIO $ runExceptT dbAction

cardano-db/src/Cardano/Db/Run.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -154,6 +154,11 @@ runDbDirectSilent dbEnv action = do
154154
Left err -> throwIO err
155155
Right value -> pure value
156156

157+
-- | Connection pool-based transaction runner
158+
--
159+
-- Uses a connection from the pool rather than the main DbEnv connection.
160+
-- Wraps operations in a transaction with logging. Designed for concurrent operations
161+
-- where multiple threads need independent database connections.
157162
runDbPoolTransLogged ::
158163
MonadUnliftIO m =>
159164
Trace IO Text ->
@@ -231,6 +236,11 @@ runDbStandaloneTransSilent source action = do
231236
runDbTransSilent dbEnv action
232237
)
233238

239+
-- | Standalone runner without transaction management
240+
--
241+
-- Self-contained runner that creates its own connection but doesn't wrap operations
242+
-- in transactions. Uses auto-commit mode. Perfect for simple operations that don't
243+
-- need ACID guarantees or tools that manage their own transaction boundaries.
234244
runDbStandaloneDirectSilent :: PGPassSource -> DbM a -> IO a
235245
runDbStandaloneDirectSilent source action = do
236246
pgconfig <- runOrThrowIO (readPGPass source)

doc/database-encode-decode.md

Lines changed: 63 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,69 @@ data DbEnv = DbEnv
1414
}
1515
```
1616

17+
## Database Execution Functions
18+
19+
Different `runDb*` functions provide various execution patterns for different use cases:
20+
21+
### Transaction-Based Runners
22+
23+
**`runDbTransLogged`** - Main synchronisation runner
24+
- Full ACID transaction guarantees with BEGIN/COMMIT/ROLLBACK
25+
- Comprehensive logging for debugging and monitoring
26+
- Primary runner for cardano-db-sync block processing
27+
- Automatically handles all transaction management
28+
29+
**`runDbTransSilent`** - Performance-focused transaction runner
30+
- Same transaction guarantees as logged version
31+
- No logging overhead for performance-critical operations
32+
- Ideal for testing scenarios or high-throughput operations
33+
34+
**`runDbPoolTransLogged`** - Concurrent transaction runner
35+
- Uses connection pool instead of main connection
36+
- Full transaction management with logging
37+
- Designed for concurrent operations where multiple threads need independent connections
38+
- Requires DbEnv with connection pool configured
39+
40+
### Direct Runners (No Transaction Management)
41+
42+
**`runDbDirectLogged`** - Auto-commit with logging
43+
- No explicit transaction management (auto-commit mode)
44+
- Each statement commits immediately
45+
- Includes logging for debugging
46+
- Use when operations manage their own transactions
47+
48+
**`runDbDirectSilent`** - Auto-commit without logging
49+
- No transaction management or logging overhead
50+
- Maximum performance for simple operations
51+
- Use for operations that don't need ACID guarantees
52+
53+
### Standalone Runners
54+
55+
**`runDbStandaloneSilent`** - Simple script runner
56+
- Self-contained with automatic connection management
57+
- Creates temporary connection from environment variables
58+
- Perfect for simple scripts and testing
59+
- Includes transaction management
60+
61+
**`runDbStandaloneTransSilent`** - Configurable standalone runner
62+
- Custom connection configuration support
63+
- Full transaction management
64+
- Automatic resource cleanup
65+
- Good for applications needing custom connection settings
66+
67+
**`runDbStandaloneDirectSilent`** - Script runner without transactions
68+
- Self-contained connection management
69+
- Auto-commit mode (no transactions)
70+
- Use for simple operations or tools that manage their own transaction boundaries
71+
72+
### Pool-Based Runners
73+
74+
**`runDbWithPool`** - External service runner
75+
- Designed for external services (like SMASH server)
76+
- Returns Either for explicit error handling (no exceptions)
77+
- Uses provided connection pool
78+
- Creates temporary DbEnv from pool connection
79+
1780
### Basic Usage
1881

1982
```haskell

0 commit comments

Comments
 (0)