@@ -74,37 +74,38 @@ import Ouroboros.Consensus.Cardano.Block (StandardCrypto)
7474-- NOTE: Other tables are not cleaned up since they are not rollbacked.
7575rollbackCache :: MonadIO m => CacheStatus -> DB. BlockId -> ReaderT SqlBackend m ()
7676rollbackCache NoCache _ = pure ()
77- rollbackCache (ActiveCache _ cache) blockId = do
77+ rollbackCache (ActiveCache cache) blockId = do
7878 liftIO $ do
7979 atomically $ writeTVar (cPrevBlock cache) Nothing
8080 atomically $ modifyTVar (cDatum cache) LRU. cleanup
8181 atomically $ modifyTVar (cTxIds cache) FIFO. cleanupCache
8282 void $ rollbackMapEpochInCache cache blockId
8383
84- -- When syncing and we get within 2 minutes of the tip, we can optimise the caches
85- -- and set the flag to True on ActiveCache.
84+ -- | When syncing and we get within 2 minutes of the tip, we can optimise the caches
85+ -- and set the flag to True on ActiveCache.leaving the following caches as they are:
86+ -- cPools, cPrevBlock, Cstats, cEpoch
8687optimiseCaches :: MonadIO m => CacheStatus -> ReaderT SqlBackend m CacheStatus
8788optimiseCaches cache =
8889 case cache of
8990 NoCache -> pure cache
90- ActiveCache True _ -> pure cache
91- ActiveCache False c -> do
92- liftIO $ do
93- -- empty caches not to be used anymore
94- atomically $ modifyTVar (cTxIds c) FIFO. cleanupCache
95- atomically $ writeTVar (cStake c) (StakeCache Map. empty (LRU. empty 0 ))
96- atomically $ modifyTVar (cDatum c) (LRU. optimise 0 )
97- -- empty then limit the capacity of the cache
98- atomically $ writeTVar (cMultiAssets c) (LRU. empty 50000 )
99- -- leaving the following caches as they are:
100- -- cPools, cPrevBlock, Cstats, cEpoch
101- pure $ ActiveCache True c
91+ ActiveCache c ->
92+ withCacheOptimisationCheck c ( pure cache) $
93+ liftIO $ do
94+ -- empty caches not to be used anymore
95+ atomically $ modifyTVar (cTxIds c) FIFO. cleanupCache
96+ atomically $ writeTVar (cStake c) (StakeCache Map. empty (LRU. empty 0 ))
97+ atomically $ modifyTVar (cDatum c) (LRU. optimise 0 )
98+ -- empty then limit the capacity of the cache
99+ atomically $ writeTVar (cMultiAssets c) (LRU. empty 50000 )
100+ -- set the flag to True
101+ atomically $ writeTVar (cIsCacheOptimised c) True
102+ pure $ ActiveCache c
102103
103104getCacheStatistics :: CacheStatus -> IO CacheStatistics
104105getCacheStatistics cs =
105106 case cs of
106107 NoCache -> pure initCacheStatistics
107- ActiveCache _ ci -> readTVarIO (cStats ci)
108+ ActiveCache ci -> readTVarIO (cStats ci)
108109
109110queryOrInsertRewardAccount ::
110111 (MonadBaseControl IO m , MonadIO m ) =>
@@ -171,33 +172,33 @@ queryStakeAddrWithCacheRetBs _trce cache cacheUA ra@(Ledger.RewardAccount _ cred
171172 let bs = Ledger. serialiseRewardAccount ra
172173 case cache of
173174 NoCache -> mapLeft (,bs) <$> resolveStakeAddress bs
174- ActiveCache True _ -> mapLeft (,bs) <$> resolveStakeAddress bs
175- ActiveCache False ci -> do
176- stakeCache <- liftIO $ readTVarIO (cStake ci)
177- case queryStakeCache cred stakeCache of
178- Just (addrId, stakeCache') -> do
179- liftIO $ hitCreds (cStats ci)
180- case cacheUA of
181- EvictAndUpdateCache -> do
182- liftIO $ atomically $ writeTVar (cStake ci) $ deleteStakeCache cred stakeCache'
183- pure $ Right addrId
184- _other -> do
185- liftIO $ atomically $ writeTVar (cStake ci) stakeCache'
186- pure $ Right addrId
187- Nothing -> do
188- queryRes <- mapLeft (,bs) <$> resolveStakeAddress bs
189- liftIO $ missCreds (cStats ci)
190- case queryRes of
191- Left _ -> pure queryRes
192- Right stakeAddrsId -> do
193- let ! stakeCache' = case cacheUA of
194- UpdateCache -> stakeCache {scLruCache = LRU. insert cred stakeAddrsId (scLruCache stakeCache)}
195- UpdateCacheStrong -> stakeCache {scStableCache = Map. insert cred stakeAddrsId (scStableCache stakeCache)}
196- _ -> stakeCache
197- liftIO $
198- atomically $
199- writeTVar (cStake ci) stakeCache'
200- pure $ Right stakeAddrsId
175+ ActiveCache ci -> do
176+ withCacheOptimisationCheck ci (mapLeft (,bs) <$> resolveStakeAddress bs) $ do
177+ stakeCache <- liftIO $ readTVarIO (cStake ci)
178+ case queryStakeCache cred stakeCache of
179+ Just (addrId, stakeCache') -> do
180+ liftIO $ hitCreds (cStats ci)
181+ case cacheUA of
182+ EvictAndUpdateCache -> do
183+ liftIO $ atomically $ writeTVar (cStake ci) $ deleteStakeCache cred stakeCache'
184+ pure $ Right addrId
185+ _other -> do
186+ liftIO $ atomically $ writeTVar (cStake ci) stakeCache'
187+ pure $ Right addrId
188+ Nothing -> do
189+ queryRes <- mapLeft (,bs) <$> resolveStakeAddress bs
190+ liftIO $ missCreds (cStats ci)
191+ case queryRes of
192+ Left _ -> pure queryRes
193+ Right stakeAddrsId -> do
194+ let ! stakeCache' = case cacheUA of
195+ UpdateCache -> stakeCache {scLruCache = LRU. insert cred stakeAddrsId (scLruCache stakeCache)}
196+ UpdateCacheStrong -> stakeCache {scStableCache = Map. insert cred stakeAddrsId (scStableCache stakeCache)}
197+ _ -> stakeCache
198+ liftIO $
199+ atomically $
200+ writeTVar (cStake ci) stakeCache'
201+ pure $ Right stakeAddrsId
201202
202203-- | True if it was found in LRU
203204queryStakeCache :: StakeCred -> StakeCache -> Maybe (DB. StakeAddressId , StakeCache )
@@ -224,7 +225,7 @@ queryPoolKeyWithCache cache cacheUA hsh =
224225 case mPhId of
225226 Nothing -> pure $ Left (DB. DbLookupMessage " PoolKeyHash" )
226227 Just phId -> pure $ Right phId
227- ActiveCache _ ci -> do
228+ ActiveCache ci -> do
228229 mp <- liftIO $ readTVarIO (cPools ci)
229230 case Map. lookup hsh mp of
230231 Just phId -> do
@@ -264,7 +265,7 @@ insertPoolKeyWithCache cache cacheUA pHash =
264265 { DB. poolHashHashRaw = Generic. unKeyHashRaw pHash
265266 , DB. poolHashView = Generic. unKeyHashView pHash
266267 }
267- ActiveCache _ ci -> do
268+ ActiveCache ci -> do
268269 mp <- liftIO $ readTVarIO (cPools ci)
269270 case Map. lookup pHash mp of
270271 Just phId -> do
@@ -327,23 +328,23 @@ queryMAWithCache ::
327328queryMAWithCache cache policyId asset =
328329 case cache of
329330 NoCache -> queryDb
330- ActiveCache True _ -> queryDb
331- ActiveCache False ci -> do
332- mp <- liftIO $ readTVarIO (cMultiAssets ci)
333- case LRU. lookup (policyId, asset) mp of
334- Just (maId, mp') -> do
335- liftIO $ hitMAssets (cStats ci)
336- liftIO $ atomically $ writeTVar (cMultiAssets ci) mp'
337- pure $ Right maId
338- Nothing -> do
339- liftIO $ missMAssets (cStats ci)
340- -- miss. The lookup doesn't change the cache on a miss.
341- let ! policyBs = Generic. unScriptHash $ policyID policyId
342- let ! assetNameBs = Generic. unAssetName asset
343- maId <- maybe (Left (policyBs, assetNameBs)) Right <$> DB. queryMultiAssetId policyBs assetNameBs
344- whenRight maId $
345- liftIO . atomically . modifyTVar (cMultiAssets ci) . LRU. insert (policyId, asset)
346- pure maId
331+ ActiveCache ci -> do
332+ withCacheOptimisationCheck ci queryDb $ do
333+ mp <- liftIO $ readTVarIO (cMultiAssets ci)
334+ case LRU. lookup (policyId, asset) mp of
335+ Just (maId, mp') -> do
336+ liftIO $ hitMAssets (cStats ci)
337+ liftIO $ atomically $ writeTVar (cMultiAssets ci) mp'
338+ pure $ Right maId
339+ Nothing -> do
340+ liftIO $ missMAssets (cStats ci)
341+ -- miss. The lookup doesn't change the cache on a miss.
342+ let ! policyBs = Generic. unScriptHash $ policyID policyId
343+ let ! assetNameBs = Generic. unAssetName asset
344+ maId <- maybe (Left (policyBs, assetNameBs)) Right <$> DB. queryMultiAssetId policyBs assetNameBs
345+ whenRight maId $
346+ liftIO . atomically . modifyTVar (cMultiAssets ci) . LRU. insert (policyId, asset)
347+ pure maId
347348 where
348349 queryDb = do
349350 let ! policyBs = Generic. unScriptHash $ policyID policyId
@@ -359,7 +360,7 @@ queryPrevBlockWithCache ::
359360queryPrevBlockWithCache msg cache hsh =
360361 case cache of
361362 NoCache -> liftLookupFail msg $ DB. queryBlockId hsh
362- ActiveCache _ ci -> do
363+ ActiveCache ci -> do
363364 mCachedPrev <- liftIO $ readTVarIO (cPrevBlock ci)
364365 case mCachedPrev of
365366 -- if the cached block matches the requested hash, we return its db id.
@@ -388,28 +389,28 @@ queryTxIdWithCache cache txIdLedger = do
388389 case cache of
389390 -- Direct database query if no cache.
390391 NoCache -> qTxHash
391- ActiveCache True _ -> qTxHash
392- ActiveCache False cacheInternal -> do
393- -- Read current cache state.
394- cacheTx <- liftIO $ readTVarIO (cTxIds cacheInternal )
395-
396- case FIFO. lookup txIdLedger cacheTx of
397- -- Cache hit, return the transaction ID.
398- Just txId -> do
399- liftIO $ hitTxIds (cStats cacheInternal )
400- pure $ Right txId
401- -- Cache miss.
402- Nothing -> do
403- eTxId <- qTxHash
404- liftIO $ missTxIds (cStats cacheInternal )
405- case eTxId of
406- Right txId -> do
407- -- Update cache.
408- liftIO $ atomically $ modifyTVar (cTxIds cacheInternal ) $ FIFO. insert txIdLedger txId
409- -- Return ID after updating cache.
410- pure $ Right txId
411- -- Return lookup failure.
412- Left _ -> pure $ Left $ DB. DbLookupTxHash txHash
392+ ActiveCache ci ->
393+ withCacheOptimisationCheck ci qTxHash $ do
394+ -- Read current cache state.
395+ cacheTx <- liftIO $ readTVarIO (cTxIds ci )
396+
397+ case FIFO. lookup txIdLedger cacheTx of
398+ -- Cache hit, return the transaction ID.
399+ Just txId -> do
400+ liftIO $ hitTxIds (cStats ci )
401+ pure $ Right txId
402+ -- Cache miss.
403+ Nothing -> do
404+ eTxId <- qTxHash
405+ liftIO $ missTxIds (cStats ci )
406+ case eTxId of
407+ Right txId -> do
408+ -- Update cache.
409+ liftIO $ atomically $ modifyTVar (cTxIds ci ) $ FIFO. insert txIdLedger txId
410+ -- Return ID after updating cache.
411+ pure $ Right txId
412+ -- Return lookup failure.
413+ Left _ -> pure $ Left $ DB. DbLookupTxHash txHash
413414 where
414415 txHash = Generic. unTxHash txIdLedger
415416 qTxHash = DB. queryTxId txHash
@@ -420,7 +421,7 @@ tryUpdateCacheTx ::
420421 Ledger. TxId StandardCrypto ->
421422 DB. TxId ->
422423 m ()
423- tryUpdateCacheTx (ActiveCache False ci) ledgerTxId txId =
424+ tryUpdateCacheTx (ActiveCache ci) ledgerTxId txId =
424425 liftIO $ atomically $ modifyTVar (cTxIds ci) $ FIFO. insert ledgerTxId txId
425426tryUpdateCacheTx _ _ _ = pure ()
426427
@@ -432,13 +433,13 @@ insertBlockAndCache ::
432433insertBlockAndCache cache block =
433434 case cache of
434435 NoCache -> insBlck
435- ActiveCache True _ -> insBlck
436- ActiveCache False ci -> do
437- bid <- insBlck
438- liftIO $ do
439- missPrevBlock (cStats ci)
440- atomically $ writeTVar (cPrevBlock ci) $ Just (bid, DB. blockHash block)
441- pure bid
436+ ActiveCache ci ->
437+ withCacheOptimisationCheck ci insBlck $ do
438+ bid <- insBlck
439+ liftIO $ do
440+ missPrevBlock (cStats ci)
441+ atomically $ writeTVar (cPrevBlock ci) $ Just (bid, DB. blockHash block)
442+ pure bid
442443 where
443444 insBlck = DB. insertBlock block
444445
@@ -450,18 +451,18 @@ queryDatum ::
450451queryDatum cache hsh = do
451452 case cache of
452453 NoCache -> queryDtm
453- ActiveCache True _ -> queryDtm
454- ActiveCache False ci -> do
455- mp <- liftIO $ readTVarIO (cDatum ci)
456- case LRU. lookup hsh mp of
457- Just (datumId, mp') -> do
458- liftIO $ hitDatum (cStats ci)
459- liftIO $ atomically $ writeTVar (cDatum ci) mp'
460- pure $ Just datumId
461- Nothing -> do
462- liftIO $ missDatum (cStats ci)
463- -- miss. The lookup doesn't change the cache on a miss.
464- queryDtm
454+ ActiveCache ci -> do
455+ withCacheOptimisationCheck ci queryDtm $ do
456+ mp <- liftIO $ readTVarIO (cDatum ci)
457+ case LRU. lookup hsh mp of
458+ Just (datumId, mp') -> do
459+ liftIO $ hitDatum (cStats ci)
460+ liftIO $ atomically $ writeTVar (cDatum ci) mp'
461+ pure $ Just datumId
462+ Nothing -> do
463+ liftIO $ missDatum (cStats ci)
464+ -- miss. The lookup doesn't change the cache on a miss.
465+ queryDtm
465466 where
466467 queryDtm = DB. queryDatum $ Generic. dataHashToBytes hsh
467468
@@ -476,13 +477,25 @@ insertDatumAndCache cache hsh dt = do
476477 datumId <- DB. insertDatum dt
477478 case cache of
478479 NoCache -> pure datumId
479- ActiveCache True _ -> pure datumId
480- ActiveCache False ci -> do
481- liftIO $
482- atomically $
483- modifyTVar (cDatum ci) $
484- LRU. insert hsh datumId
485- pure datumId
480+ ActiveCache ci ->
481+ withCacheOptimisationCheck ci (pure datumId) $ do
482+ liftIO $
483+ atomically $
484+ modifyTVar (cDatum ci) $
485+ LRU. insert hsh datumId
486+ pure datumId
487+
488+ withCacheOptimisationCheck ::
489+ MonadIO m =>
490+ CacheInternal ->
491+ m a -> -- Action to perform if cache is optimised
492+ m a -> -- Action to perform if cache is not optimised
493+ m a
494+ withCacheOptimisationCheck ci ifOptimised ifNotOptimised = do
495+ isCachedOptimised <- liftIO $ readTVarIO (cIsCacheOptimised ci)
496+ if isCachedOptimised
497+ then ifOptimised
498+ else ifNotOptimised
486499
487500-- Stakes
488501hitCreds :: StrictTVar IO CacheStatistics -> IO ()
0 commit comments