@@ -18,14 +18,12 @@ module Ouroboros.Consensus.Storage.LedgerDB.V2 (mkInitDb) where
18
18
19
19
import Cardano.Ledger.BaseTypes (unNonZero )
20
20
import Control.Arrow ((>>>) )
21
- import Control.Monad (join )
22
- import qualified Control.Monad as Monad (void , (>=>) )
21
+ import qualified Control.Monad as Monad (join , void )
23
22
import Control.Monad.Except
24
23
import Control.RAWLock
25
24
import qualified Control.RAWLock as RAWLock
26
25
import Control.ResourceRegistry
27
26
import Control.Tracer
28
- import Data.Foldable (traverse_ )
29
27
import qualified Data.Foldable as Foldable
30
28
import Data.Functor.Contravariant ((>$<) )
31
29
import Data.Kind (Type )
@@ -195,7 +193,7 @@ mkInternals bss h =
195
193
let selectWhereTo = case whereTo of
196
194
TakeAtImmutableTip -> anchorHandle
197
195
TakeAtVolatileTip -> currentHandle
198
- withStateRef env (MkSolo . selectWhereTo) $ \ (MkSolo st ) ->
196
+ withStateRef env (MkSolo . selectWhereTo) $ \ (MkSolo (st, _) ) ->
199
197
Monad. void $
200
198
takeSnapshot
201
199
(configCodec . getExtLedgerCfg . ledgerDbCfg $ ldbCfg env)
@@ -249,7 +247,7 @@ mkInternals bss h =
249
247
250
248
pruneLedgerSeq :: LedgerDBEnv m (ExtLedgerState blk ) blk -> m ()
251
249
pruneLedgerSeq env =
252
- join $ atomically $ stateTVar (ldbSeq env) $ pruneToImmTipOnly
250
+ Monad. join $ atomically $ stateTVar (ldbSeq env) $ pruneToImmTipOnly
253
251
254
252
-- | Testing only! Truncate all snapshots in the DB.
255
253
implIntTruncateSnapshots :: MonadThrow m => SomeHasFS m -> m ()
@@ -360,7 +358,7 @@ implGarbageCollect env slotNo = do
360
358
Set. dropWhileAntitone ((< slotNo) . realPointSlot)
361
359
-- It is safe to close the handles outside of the locked region, which reduces
362
360
-- contention. See the docs of 'ldbOpenHandlesLock'.
363
- join $ RAWLock. withWriteAccess (ldbOpenHandlesLock env) $ \ () -> do
361
+ Monad. join $ RAWLock. withWriteAccess (ldbOpenHandlesLock env) $ \ () -> do
364
362
close <- atomically $ stateTVar (ldbSeq env) $ prune (LedgerDbPruneBeforeSlot slotNo)
365
363
pure (close, () )
366
364
@@ -379,7 +377,7 @@ implTryTakeSnapshot ::
379
377
implTryTakeSnapshot bss env mTime nrBlocks =
380
378
if onDiskShouldTakeSnapshot (ldbSnapshotPolicy env) (uncurry (flip diffTime) <$> mTime) nrBlocks
381
379
then do
382
- withStateRef env (MkSolo . anchorHandle) $ \ (MkSolo st ) ->
380
+ withStateRef env (MkSolo . anchorHandle) $ \ (MkSolo (st, _) ) ->
383
381
Monad. void $
384
382
takeSnapshot
385
383
(configCodec . getExtLedgerCfg . ledgerDbCfg $ ldbCfg env)
@@ -585,36 +583,37 @@ getVolatileLedgerSeq env =
585
583
where
586
584
k = unNonZero $ maxRollbacks $ ledgerDbCfgSecParam $ ldbCfg env
587
585
588
- -- | Get a 'StateRef' from the 'LedgerSeq' (via 'getVolatileLedgerSeq') in the
589
- -- 'LedgerDBEnv', with the ' LedgerTablesHandle' having been duplicated (such
590
- -- that the original can be closed). The caller is responsible for closing the
591
- -- handle.
586
+ -- | Get a 'StateRef' from the 'LedgerSeq' in the 'LedgerDBEnv', with the
587
+ -- 'LedgerTablesHandle' having been duplicated (such that the original can be
588
+ -- closed). The caller should close the handle using the returned @ResourceKey@,
589
+ -- although closing the registry will also release the handle.
592
590
--
593
591
-- For more flexibility, an arbitrary 'Traversable' of the 'StateRef' can be
594
592
-- returned; for the simple use case of getting a single 'StateRef', use @t ~
595
593
-- 'Solo'@.
596
594
getStateRef ::
597
595
(IOLike m , Traversable t , GetTip l ) =>
598
596
LedgerDBEnv m l blk ->
597
+ ResourceRegistry m ->
599
598
(LedgerSeq m l -> t (StateRef m l )) ->
600
- m (t (StateRef m l ))
601
- getStateRef ldbEnv project =
599
+ m (t (StateRef m l , ResourceKey m ))
600
+ getStateRef ldbEnv reg project =
602
601
RAWLock. withReadAccess (ldbOpenHandlesLock ldbEnv) $ \ () -> do
603
602
tst <- project <$> atomically (getVolatileLedgerSeq ldbEnv)
604
603
for tst $ \ st -> do
605
- tables' <- duplicate $ tables st
606
- pure st{tables = tables'}
604
+ (resKey, tables') <- allocate reg ( \ _ -> duplicate $ tables st) close
605
+ pure ( st{tables = tables'}, resKey)
607
606
608
607
-- | Like 'StateRef', but takes care of closing the handle when the given action
609
608
-- returns or errors.
610
609
withStateRef ::
611
610
(IOLike m , Traversable t , GetTip l ) =>
612
611
LedgerDBEnv m l blk ->
613
612
(LedgerSeq m l -> t (StateRef m l )) ->
614
- (t (StateRef m l ) -> m a ) ->
613
+ (t (StateRef m l , ResourceKey m ) -> m a ) ->
615
614
m a
616
- withStateRef ldbEnv project =
617
- bracket ( getStateRef ldbEnv project) (traverse_ (close . tables))
615
+ withStateRef ldbEnv project f =
616
+ withRegistry $ \ reg -> getStateRef ldbEnv reg project >>= f
618
617
619
618
acquireAtTarget ::
620
619
( HeaderHash l ~ HeaderHash blk
@@ -625,9 +624,10 @@ acquireAtTarget ::
625
624
) =>
626
625
LedgerDBEnv m l blk ->
627
626
Either Word64 (Target (Point blk )) ->
628
- m (Either GetForkerError (StateRef m l ))
629
- acquireAtTarget ldbEnv target =
630
- getStateRef ldbEnv $ \ l -> case target of
627
+ ResourceRegistry m ->
628
+ m (Either GetForkerError (StateRef m l , ResourceKey m ))
629
+ acquireAtTarget ldbEnv target reg =
630
+ getStateRef ldbEnv reg $ \ l -> case target of
631
631
Right VolatileTip -> pure $ currentHandle l
632
632
Right ImmutableTip -> pure $ anchorHandle l
633
633
Right (SpecificPoint pt) -> do
@@ -661,7 +661,7 @@ newForkerAtTarget ::
661
661
Target (Point blk ) ->
662
662
m (Either GetForkerError (Forker m l blk ))
663
663
newForkerAtTarget h rr pt = getEnv h $ \ ldbEnv ->
664
- acquireAtTarget ldbEnv (Right pt) >>= traverse (newForker h ldbEnv rr)
664
+ acquireAtTarget ldbEnv (Right pt) rr >>= traverse (newForker h ldbEnv rr)
665
665
666
666
newForkerByRollback ::
667
667
( HeaderHash l ~ HeaderHash blk
@@ -676,14 +676,14 @@ newForkerByRollback ::
676
676
Word64 ->
677
677
m (Either GetForkerError (Forker m l blk ))
678
678
newForkerByRollback h rr n = getEnv h $ \ ldbEnv ->
679
- acquireAtTarget ldbEnv (Left n) >>= traverse (newForker h ldbEnv rr)
679
+ acquireAtTarget ldbEnv (Left n) rr >>= traverse (newForker h ldbEnv rr)
680
680
681
681
closeForkerEnv ::
682
682
IOLike m => ForkerEnv m l blk -> m ()
683
683
closeForkerEnv ForkerEnv {foeResourcesToRelease = (lock, key, toRelease)} =
684
684
RAWLock. withWriteAccess lock $
685
685
const $ do
686
- id =<< atomically (swapTVar toRelease (pure () ))
686
+ Monad. join $ atomically (swapTVar toRelease (pure () ))
687
687
_ <- release key
688
688
pure (() , () )
689
689
@@ -773,14 +773,19 @@ newForker ::
773
773
LedgerDBHandle m l blk ->
774
774
LedgerDBEnv m l blk ->
775
775
ResourceRegistry m ->
776
- StateRef m l ->
776
+ ( StateRef m l , ResourceKey m ) ->
777
777
m (Forker m l blk )
778
- newForker h ldbEnv rr st = do
778
+ newForker h ldbEnv rr (st, rk) = do
779
779
forkerKey <- atomically $ stateTVar (ldbNextForkerKey ldbEnv) $ \ r -> (r, r + 1 )
780
780
let tr = LedgerDBForkerEvent . TraceForkerEventWithKey forkerKey >$< ldbTracer ldbEnv
781
781
traceWith tr ForkerOpen
782
782
lseqVar <- newTVarIO . LedgerSeq . AS. Empty $ st
783
- (k, toRelease) <- allocate rr (\ _ -> newTVarIO (pure () )) (readTVarIO Monad. >=> id )
783
+ -- The closing action that we allocate in the TVar from the start is not
784
+ -- strictly necessary if the caller uses a short-lived registry like the ones
785
+ -- in Chain selection or the forging loop. Just in case the user passes a
786
+ -- long-lived registry, we store such closing action to make sure the handle
787
+ -- is closed even under @forkerClose@ if the registry outlives the forker.
788
+ (k, toRelease) <- allocate rr (\ _ -> newTVarIO (Monad. void (release rk))) (Monad. join . readTVarIO)
784
789
let forkerEnv =
785
790
ForkerEnv
786
791
{ foeLedgerSeq = lseqVar
0 commit comments