Skip to content

Commit 54e8f11

Browse files
committed
proper cache optimisation
1 parent 97bbf3f commit 54e8f11

File tree

8 files changed

+72
-53
lines changed

8 files changed

+72
-53
lines changed

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

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -321,6 +321,8 @@ mkSyncEnv metricSetters trce dbEnv syncOptions protoInfo nw nwMagic systemStart
321321
, cacheCapacityDatum = 125000
322322
, cacheCapacityMultiAsset = 125000
323323
, cacheCapacityTx = 50000
324+
, cacheOptimisePools = 50000
325+
, cacheOptimiseStake = 50000
324326
}
325327
else pure useNoCache
326328
consistentLevelVar <- newTVarIO Unchecked

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

Lines changed: 39 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ module Cardano.DbSync.Cache (
2323
queryStakeAddrWithCache,
2424
queryTxIdWithCache,
2525
rollbackCache,
26+
cleanCachesForTip,
2627
optimiseCaches,
2728
tryUpdateCacheTx,
2829
) where
@@ -80,15 +81,15 @@ rollbackCache (ActiveCache cache) blockId = do
8081
atomically $ modifyTVar (cTxIds cache) FIFO.cleanupCache
8182
void $ rollbackMapEpochInCache cache blockId
8283

83-
-- | When syncing and we get within 2 minutes of the tip, we can optimise the caches
84-
-- and set the flag to True on ActiveCache.leaving the following caches as they are:
85-
-- cPools, cPrevBlock, Cstats, cEpoch
86-
optimiseCaches :: CacheStatus -> ExceptT SyncNodeError DB.DbM ()
87-
optimiseCaches cache =
84+
-- | When syncing and we get within 2 minutes of the tip, we clean certain caches
85+
-- and set the flag to True on ActiveCache. We disable the following caches:
86+
-- cStake, cDatum, cAddress. We keep: cPools, cPrevBlock, cMultiAssets, cEpoch, cTxIds
87+
cleanCachesForTip :: CacheStatus -> ExceptT SyncNodeError DB.DbM ()
88+
cleanCachesForTip cache =
8889
case cache of
8990
NoCache -> pure ()
9091
ActiveCache c ->
91-
withCacheOptimisationCheck c (pure ()) $
92+
withCacheCleanedForTipCheck c (pure ()) $
9293
liftIO $ do
9394
-- empty caches not to be used anymore
9495
atomically $ modifyTVar (cTxIds c) FIFO.cleanupCache
@@ -97,9 +98,26 @@ optimiseCaches cache =
9798
-- empty then limit the capacity of the cache
9899
atomically $ writeTVar (cMultiAssets c) (LRU.empty 50000)
99100
-- set the flag to True
100-
atomically $ writeTVar (cIsCacheOptimised c) True
101+
atomically $ writeTVar (cIsCacheCleanedForTip c) True
101102
pure ()
102103

104+
-- | Optimise caches during syncing to prevent unbounded growth.
105+
-- This function trims Map-based caches that can grow without bounds.
106+
-- LRU caches are skipped as they have built-in capacity limits.
107+
optimiseCaches :: CacheStatus -> ExceptT SyncNodeError DB.DbM ()
108+
optimiseCaches cache =
109+
case cache of
110+
NoCache -> pure ()
111+
ActiveCache c -> do
112+
liftIO $ do
113+
-- Trim pools Map to target size (keep most recent entries)
114+
atomically $ modifyTVar (cPools c) $ \poolMap ->
115+
Map.fromList $ take (fromIntegral $ cOptimisePools c) $ Map.toList poolMap
116+
117+
-- Trim stake stable cache to target size
118+
atomically $ modifyTVar (cStake c) $ \stakeCache ->
119+
stakeCache { scStableCache = Map.fromList $ take (fromIntegral $ cOptimiseStake c) $ Map.toList (scStableCache stakeCache) }
120+
103121
queryOrInsertRewardAccount ::
104122
SyncEnv ->
105123
CacheAction ->
@@ -156,7 +174,7 @@ queryStakeAddrWithCacheRetBs syncEnv cacheUA ra@(Ledger.RewardAccount _ cred) =
156174
case envCache syncEnv of
157175
NoCache -> (,bs) <$> resolveStakeAddress bs
158176
ActiveCache ci -> do
159-
result <- withCacheOptimisationCheck ci (resolveStakeAddress bs) $ do
177+
result <- withCacheCleanedForTipCheck ci (resolveStakeAddress bs) $ do
160178
stakeCache <- liftIO $ readTVarIO (cStake ci)
161179
case queryStakeCache cred stakeCache of
162180
Just (addrId, stakeCache') -> do
@@ -364,7 +382,7 @@ queryMAWithCache syncEnv policyId asset =
364382
case envCache syncEnv of
365383
NoCache -> lift queryDb
366384
ActiveCache ci -> do
367-
withCacheOptimisationCheck ci (lift queryDb) $ do
385+
withCacheCleanedForTipCheck ci (lift queryDb) $ do
368386
mp <- liftIO $ readTVarIO (cMultiAssets ci)
369387
case LRU.lookup (policyId, asset) mp of
370388
Just (maId, mp') -> do
@@ -424,7 +442,7 @@ queryTxIdWithCache syncEnv txIdLedger = do
424442
-- Direct database query if no cache.
425443
NoCache -> lift qTxHash
426444
ActiveCache ci ->
427-
withCacheOptimisationCheck ci (lift qTxHash) $ do
445+
withCacheCleanedForTipCheck ci (lift qTxHash) $ do
428446
-- Read current cache state.
429447
cacheTx <- liftIO $ readTVarIO (cTxIds ci)
430448

@@ -472,7 +490,7 @@ insertBlockAndCache syncEnv block =
472490
case envCache syncEnv of
473491
NoCache -> lift insBlck
474492
ActiveCache ci ->
475-
withCacheOptimisationCheck ci (lift insBlck) $ do
493+
withCacheCleanedForTipCheck ci (lift insBlck) $ do
476494
bid <- lift insBlck
477495
liftIO $ do
478496
missPrevBlock syncEnv
@@ -489,7 +507,7 @@ queryDatum syncEnv hsh = do
489507
case envCache syncEnv of
490508
NoCache -> lift queryDtm
491509
ActiveCache ci -> do
492-
withCacheOptimisationCheck ci (lift queryDtm) $ do
510+
withCacheCleanedForTipCheck ci (lift queryDtm) $ do
493511
mp <- liftIO $ readTVarIO (cDatum ci)
494512
case LRU.lookup hsh mp of
495513
Just (datumId, mp') -> do
@@ -514,24 +532,24 @@ insertDatumAndCache cache hsh dt = do
514532
case cache of
515533
NoCache -> pure datumId
516534
ActiveCache ci ->
517-
withCacheOptimisationCheck ci (pure datumId) $ do
535+
withCacheCleanedForTipCheck ci (pure datumId) $ do
518536
liftIO $
519537
atomically $
520538
modifyTVar (cDatum ci) $
521539
LRU.insert hsh datumId
522540
pure datumId
523541

524-
withCacheOptimisationCheck ::
542+
withCacheCleanedForTipCheck ::
525543
MonadIO m =>
526544
CacheInternal ->
527-
m a -> -- Action to perform if cache is optimised
528-
m a -> -- Action to perform if cache is not optimised
545+
m a -> -- Action to perform if cache is cleaned for tip
546+
m a -> -- Action to perform if cache is not cleaned for tip
529547
m a
530-
withCacheOptimisationCheck ci ifOptimised ifNotOptimised = do
531-
isCachedOptimised <- liftIO $ readTVarIO (cIsCacheOptimised ci)
532-
if isCachedOptimised
533-
then ifOptimised
534-
else ifNotOptimised
548+
withCacheCleanedForTipCheck ci ifCleanedForTip ifNotCleanedForTip = do
549+
isCacheCleanedForTip <- liftIO $ readTVarIO (cIsCacheCleanedForTip ci)
550+
if isCacheCleanedForTip
551+
then ifCleanedForTip
552+
else ifNotCleanedForTip
535553

536554
-- Creds
537555
hitCreds :: SyncEnv -> IO ()

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

Lines changed: 13 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -73,7 +73,7 @@ data CacheAction
7373
deriving (Eq)
7474

7575
data CacheInternal = CacheInternal
76-
{ cIsCacheOptimised :: !(StrictTVar IO Bool)
76+
{ cIsCacheCleanedForTip :: !(StrictTVar IO Bool)
7777
, cStake :: !(StrictTVar IO StakeCache)
7878
, cPools :: !(StrictTVar IO StakePoolCache)
7979
, cDatum :: !(StrictTVar IO (LRUCache DataHash DB.DatumId))
@@ -82,6 +82,9 @@ data CacheInternal = CacheInternal
8282
, cEpoch :: !(StrictTVar IO CacheEpoch)
8383
, cAddress :: !(StrictTVar IO (LRUCache ByteString DB.AddressId))
8484
, cTxIds :: !(StrictTVar IO (FIFOCache Ledger.TxId DB.TxId))
85+
-- Optimisation target sizes for Map-based caches
86+
, cOptimisePools :: !Word64
87+
, cOptimiseStake :: !Word64
8588
}
8689

8790
data CacheStatistics = CacheStatistics
@@ -108,6 +111,9 @@ data CacheCapacity = CacheCapacity
108111
, cacheCapacityDatum :: !Word64
109112
, cacheCapacityMultiAsset :: !Word64
110113
, cacheCapacityTx :: !Word64
114+
-- Optimisation target sizes for Map-based caches (used every 100k blocks)
115+
, cacheOptimisePools :: !Word64
116+
, cacheOptimiseStake :: !Word64
111117
}
112118

113119
-- When inserting Txs and Blocks we also caculate values which can later be used when calculating a Epochs.
@@ -132,7 +138,7 @@ data CacheEpoch = CacheEpoch
132138
textShowCacheStats :: CacheStatistics -> CacheStatus -> IO Text
133139
textShowCacheStats _ NoCache = pure "No Caches"
134140
textShowCacheStats stats (ActiveCache ic) = do
135-
isCacheOptimised <- readTVarIO $ cIsCacheOptimised ic
141+
isCacheCleanedForTip <- readTVarIO $ cIsCacheCleanedForTip ic
136142
stakeHashRaws <- readTVarIO (cStake ic)
137143
pools <- readTVarIO (cPools ic)
138144
datums <- readTVarIO (cDatum ic)
@@ -142,7 +148,7 @@ textShowCacheStats stats (ActiveCache ic) = do
142148
pure $
143149
mconcat
144150
[ "\n\nEpoch Cache Statistics: "
145-
, "\n Caches Optimised: " <> textShow isCacheOptimised
151+
, "\n Caches Cleaned For Tip: " <> textShow isCacheCleanedForTip
146152
, textCacheSection " Stake Addresses" (scLruCache stakeHashRaws) (scStableCache stakeHashRaws) (credsHits stats) (credsQueries stats)
147153
, textMapSection " Pools" pools (poolsHits stats) (poolsQueries stats)
148154
, textLruSection " Datums" datums (datumHits stats) (datumQueries stats)
@@ -215,7 +221,7 @@ useNoCache = NoCache
215221

216222
newEmptyCache :: MonadIO m => CacheCapacity -> m CacheStatus
217223
newEmptyCache CacheCapacity {..} = liftIO $ do
218-
cIsCacheOptimised <- newTVarIO False
224+
cIsCacheCleanedForTip <- newTVarIO False
219225
cStake <- newTVarIO (StakeCache Map.empty (LRU.empty cacheCapacityStake))
220226
cPools <- newTVarIO Map.empty
221227
cDatum <- newTVarIO (LRU.empty cacheCapacityDatum)
@@ -227,7 +233,7 @@ newEmptyCache CacheCapacity {..} = liftIO $ do
227233

228234
pure . ActiveCache $
229235
CacheInternal
230-
{ cIsCacheOptimised = cIsCacheOptimised
236+
{ cIsCacheCleanedForTip = cIsCacheCleanedForTip
231237
, cStake = cStake
232238
, cPools = cPools
233239
, cDatum = cDatum
@@ -236,6 +242,8 @@ newEmptyCache CacheCapacity {..} = liftIO $ do
236242
, cEpoch = cEpoch
237243
, cAddress = cAddress
238244
, cTxIds = cTxIds
245+
, cOptimisePools = cacheOptimisePools
246+
, cOptimiseStake = cacheOptimiseStake
239247
}
240248

241249
initCacheStatistics :: CacheStatistics

cardano-db-sync/src/Cardano/DbSync/Era/Universal/Block.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ import qualified Cardano.Db as DB
2424
import Cardano.DbSync.Api
2525
import Cardano.DbSync.Api.Types (InsertOptions (..), SyncEnv (..), SyncOptions (..))
2626
import Cardano.DbSync.Cache (
27+
cleanCachesForTip,
2728
insertBlockAndCache,
2829
optimiseCaches,
2930
queryPoolKeyWithCache,
@@ -61,8 +62,8 @@ insertBlockUniversal ::
6162
ApplyResult ->
6263
ExceptT SyncNodeError DB.DbM ()
6364
insertBlockUniversal syncEnv shouldLog withinTwoMins withinHalfHour blk details isMember applyResult = do
64-
-- if we're syncing within 2 mins of the tip, we optimise the caches.
65-
when (isSyncedWithintwoMinutes details) $ optimiseCaches cache
65+
-- if we're syncing within 2 mins of the tip, we clean certain caches for tip following.
66+
when (isSyncedWithintwoMinutes details) $ cleanCachesForTip cache
6667
-- Optimise caches every 100k blocks to prevent unbounded growth
6768
when (unBlockNo (Generic.blkBlockNo blk) `mod` 100000 == 0) $ optimiseCaches cache
6869
do

cardano-db/src/Cardano/Db/Statement/Base.hs

Lines changed: 4 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -263,8 +263,7 @@ queryMinBlockStmt =
263263
Text.concat
264264
[ "SELECT id, block_no"
265265
, " FROM " <> tableName (Proxy @a)
266-
, " ORDER BY id ASC"
267-
, " LIMIT 1"
266+
, " WHERE id = (SELECT MIN(id) FROM " <> tableName (Proxy @a) <> ")"
268267
]
269268

270269
decoder = HsqlD.rowMaybe $ do
@@ -393,11 +392,9 @@ queryLatestEpochNoFromBlockStmt =
393392
sql =
394393
TextEnc.encodeUtf8 $
395394
Text.concat
396-
[ "SELECT COALESCE(epoch_no, 0)::bigint"
395+
[ "SELECT COALESCE(MAX(epoch_no), 0)::bigint"
397396
, " FROM " <> blockTable
398397
, " WHERE slot_no IS NOT NULL"
399-
, " ORDER BY epoch_no DESC"
400-
, " LIMIT 1"
401398
]
402399

403400
decoder =
@@ -465,11 +462,9 @@ queryLatestSlotNoStmt =
465462
sql =
466463
TextEnc.encodeUtf8 $
467464
Text.concat
468-
[ "SELECT COALESCE(slot_no, 0)::bigint"
465+
[ "SELECT COALESCE(MAX(slot_no), 0)::bigint"
469466
, " FROM " <> blockTable
470467
, " WHERE slot_no IS NOT NULL"
471-
, " ORDER BY slot_no DESC"
472-
, " LIMIT 1"
473468
]
474469

475470
decoder =
@@ -638,11 +633,9 @@ queryLatestBlockNoStmt =
638633
sql =
639634
TextEnc.encodeUtf8 $
640635
Text.concat
641-
[ "SELECT block_no"
636+
[ "SELECT MAX(block_no)"
642637
, " FROM " <> blockTable
643638
, " WHERE block_no IS NOT NULL"
644-
, " ORDER BY block_no DESC"
645-
, " LIMIT 1"
646639
]
647640

648641
decoder = HsqlD.rowMaybe $ do

cardano-db/src/Cardano/Db/Statement/ConsumedTxOut.hs

Lines changed: 6 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -400,17 +400,13 @@ findMaxTxInIdStmt =
400400
sql =
401401
TextEnc.encodeUtf8 $
402402
Text.concat
403-
[ "WITH tip AS ("
404-
, " SELECT MAX(block_no) AS max_block_no FROM block"
403+
[ "WITH target_block_no AS ("
404+
, " SELECT MAX(block_no) - $1 AS target_block_no FROM block"
405405
, ")"
406-
, ", target_block AS ("
407-
, " SELECT id FROM block WHERE block_no = (SELECT max_block_no - $1 FROM tip)"
408-
, ")"
409-
, ", max_tx AS ("
410-
, " SELECT MAX(id) AS max_tx_id FROM tx"
411-
, " WHERE block_id <= (SELECT id FROM target_block)"
412-
, ")"
413-
, "SELECT max_tx_id FROM max_tx"
406+
, "SELECT MAX(tx.id) AS max_tx_id"
407+
, "FROM tx"
408+
, "INNER JOIN block ON tx.block_id = block.id"
409+
, "WHERE block.block_no <= (SELECT target_block_no FROM target_block_no)"
414410
]
415411

416412
encoder = fromIntegral >$< HsqlE.param (HsqlE.nonNullable HsqlE.int8)

cardano-db/src/Cardano/Db/Statement/EpochAndProtocol.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -266,8 +266,7 @@ queryLatestEpochStmt =
266266
Text.concat
267267
[ "SELECT *"
268268
, " FROM epoch"
269-
, " ORDER BY no DESC"
270-
, " LIMIT 1"
269+
, " WHERE no = (SELECT MAX(no) FROM epoch)"
271270
]
272271

273272
decoder = HsqlD.rowMaybe SEnP.epochDecoder

cardano-db/src/Cardano/Db/Statement/OffChain.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -182,8 +182,10 @@ queryPoolTickerStmt =
182182
[ "SELECT " <> offChainPoolDataTable <> ".ticker_name"
183183
, " FROM " <> offChainPoolDataTable
184184
, " WHERE " <> offChainPoolDataTable <> ".pool_id = $1"
185-
, " ORDER BY " <> offChainPoolDataTable <> ".id DESC"
186-
, " LIMIT 1"
185+
, " AND " <> offChainPoolDataTable <> ".id = ("
186+
, " SELECT MAX(id) FROM " <> offChainPoolDataTable
187+
, " WHERE pool_id = $1"
188+
, " )"
187189
]
188190

189191
queryPoolTicker :: Id.PoolHashId -> DbM (Maybe Text)

0 commit comments

Comments
 (0)