1
1
{-# LANGUAGE DeriveAnyClass #-}
2
2
{-# LANGUAGE DeriveGeneric #-}
3
3
{-# LANGUAGE FlexibleContexts #-}
4
+ {-# LANGUAGE LambdaCase #-}
4
5
{-# LANGUAGE NamedFieldPuns #-}
5
6
{-# LANGUAGE ScopedTypeVariables #-}
6
7
{-# LANGUAGE StandaloneDeriving #-}
@@ -18,6 +19,7 @@ module Ouroboros.Consensus.Storage.LedgerDB.V1.Forker
18
19
, implForkerReadTables
19
20
) where
20
21
22
+ import Control.ResourceRegistry
21
23
import Control.Tracer
22
24
import qualified Data.Map.Strict as Map
23
25
import Data.Semigroup
@@ -40,15 +42,25 @@ import Ouroboros.Consensus.Storage.LedgerDB.V1.DiffSeq
40
42
, numInserts
41
43
)
42
44
import qualified Ouroboros.Consensus.Storage.LedgerDB.V1.DiffSeq as DS
45
+ import Ouroboros.Consensus.Storage.LedgerDB.V1.Lock
43
46
import Ouroboros.Consensus.Util.IOLike
44
47
45
48
{- ------------------------------------------------------------------------------
46
49
Forkers
47
50
-------------------------------------------------------------------------------}
48
51
49
52
data ForkerEnv m l blk = ForkerEnv
50
- { foeBackingStoreValueHandle :: ! (LedgerBackingStoreValueHandle m l )
51
- -- ^ Local, consistent view of backing store
53
+ { foeBackingStoreValueHandle ::
54
+ ! ( StrictMVar
55
+ m
56
+ ( Either
57
+ (LedgerDBLock m , LedgerBackingStore m l , ResourceRegistry m )
58
+ (LedgerBackingStoreValueHandle m l )
59
+ )
60
+ )
61
+ -- ^ Either the ingredients to create a value handle or a value handle, i.e. a
62
+ -- local, consistent view of backing store. Use 'getValueHandle' to promote
63
+ -- this if needed.
52
64
, foeChangelog :: ! (StrictTVar m (DbChangelog l ))
53
65
-- ^ In memory db changelog, 'foeBackingStoreValueHandle' must refer to
54
66
-- the anchor of this changelog.
@@ -77,32 +89,58 @@ deriving instance
77
89
Close
78
90
-------------------------------------------------------------------------------}
79
91
80
- closeForkerEnv :: ForkerEnv m l blk -> m ()
81
- closeForkerEnv ForkerEnv {foeBackingStoreValueHandle} = bsvhClose foeBackingStoreValueHandle
92
+ closeForkerEnv :: IOLike m => ForkerEnv m l blk -> m ()
93
+ closeForkerEnv ForkerEnv {foeBackingStoreValueHandle} = do
94
+ either (\ (l, _, _) -> atomically . unsafeReleaseReadAccess $ l) bsvhClose
95
+ =<< takeMVar foeBackingStoreValueHandle
82
96
83
97
{- ------------------------------------------------------------------------------
84
98
Acquiring consistent views
85
99
-------------------------------------------------------------------------------}
86
100
101
+ -- | Get the value handle in a forker, creating it on demand if this is the
102
+ -- first time we access the tables.
103
+ getValueHandle :: (GetTip l , IOLike m ) => ForkerEnv m l blk -> m (LedgerBackingStoreValueHandle m l )
104
+ getValueHandle ForkerEnv {foeBackingStoreValueHandle, foeChangelog} =
105
+ modifyMVar foeBackingStoreValueHandle $ \ case
106
+ r@ (Right bsvh) -> pure (r, bsvh)
107
+ Left (l, bs, rr) -> do
108
+ -- bsvhClose is idempotent, so we let the resource call it even if the value
109
+ -- handle might have been closed somewhere else
110
+ (_, bsvh) <- allocate rr (\ _ -> bsValueHandle bs) bsvhClose
111
+ dblogSlot <- getTipSlot . changelogLastFlushedState <$> readTVarIO foeChangelog
112
+ if bsvhAtSlot bsvh == dblogSlot
113
+ then do
114
+ atomically $ unsafeReleaseReadAccess l
115
+ pure (Right bsvh, bsvh)
116
+ else
117
+ bsvhClose bsvh
118
+ >> error
119
+ ( " Critical error: Value handles are created at "
120
+ <> show (bsvhAtSlot bsvh)
121
+ <> " while the db changelog is at "
122
+ <> show dblogSlot
123
+ <> " . There is either a race condition or a logic bug"
124
+ )
125
+
87
126
implForkerReadTables ::
88
- (MonadSTM m , HasLedgerTables l , GetTip l ) =>
127
+ (IOLike m , HasLedgerTables l , GetTip l ) =>
89
128
ForkerEnv m l blk ->
90
129
LedgerTables l KeysMK ->
91
130
m (LedgerTables l ValuesMK )
92
131
implForkerReadTables env ks = do
93
132
traceWith (foeTracer env) ForkerReadTablesStart
94
133
chlog <- readTVarIO (foeChangelog env)
95
- unfwd <- readKeySetsWith lvh (changelogLastFlushedState chlog) ks
134
+ bsvh <- getValueHandle env
135
+ unfwd <- readKeySetsWith bsvh (changelogLastFlushedState chlog) ks
96
136
case forwardTableKeySets chlog unfwd of
97
137
Left _err -> error " impossible!"
98
138
Right vs -> do
99
139
traceWith (foeTracer env) ForkerReadTablesEnd
100
140
pure vs
101
- where
102
- lvh = foeBackingStoreValueHandle env
103
141
104
142
implForkerRangeReadTables ::
105
- (MonadSTM m , HasLedgerTables l ) =>
143
+ (IOLike m , GetTip l , HasLedgerTables l ) =>
106
144
QueryBatchSize ->
107
145
ForkerEnv m l blk ->
108
146
RangeQueryPrevious l ->
@@ -132,12 +170,11 @@ implForkerRangeReadTables qbs env rq0 = do
132
170
nrequested = 1 + max (BackingStore. rqCount rq) (1 + maxDeletes)
133
171
134
172
let st = changelogLastFlushedState ldb
135
- values <- BackingStore. bsvhRangeRead lvh st (rq{BackingStore. rqCount = nrequested})
173
+ bsvh <- getValueHandle env
174
+ values <- BackingStore. bsvhRangeRead bsvh st (rq{BackingStore. rqCount = nrequested})
136
175
traceWith (foeTracer env) ForkerRangeReadTablesEnd
137
176
pure $ ltliftA2 (doFixupReadResult nrequested) diffs values
138
177
where
139
- lvh = foeBackingStoreValueHandle env
140
-
141
178
rq = BackingStore. RangeQuery rq1 (fromIntegral $ defaultQueryBatchSize qbs)
142
179
143
180
rq1 = case rq0 of
@@ -230,15 +267,15 @@ implForkerGetLedgerState env = current <$> readTVar (foeChangelog env)
230
267
-- | Obtain statistics for a combination of backing store value handle and
231
268
-- changelog.
232
269
implForkerReadStatistics ::
233
- (MonadSTM m , HasLedgerTables l , GetTip l ) =>
270
+ (IOLike m , HasLedgerTables l , GetTip l ) =>
234
271
ForkerEnv m l blk ->
235
272
m (Maybe Forker. Statistics )
236
273
implForkerReadStatistics env = do
237
274
traceWith (foeTracer env) ForkerReadStatistics
238
275
dblog <- readTVarIO (foeChangelog env)
239
-
276
+ bsvh <- getValueHandle env
240
277
let seqNo = getTipSlot $ changelogLastFlushedState dblog
241
- BackingStore. Statistics {sequenceNumber = seqNo', numEntries = n} <- bsvhStat lbsvh
278
+ BackingStore. Statistics {sequenceNumber = seqNo', numEntries = n} <- bsvhStat bsvh
242
279
if seqNo /= seqNo'
243
280
then
244
281
error $
@@ -265,8 +302,6 @@ implForkerReadStatistics env = do
265
302
Forker. Statistics
266
303
{ ledgerTableSize = n + nInserts - nDeletes
267
304
}
268
- where
269
- lbsvh = foeBackingStoreValueHandle env
270
305
271
306
implForkerPush ::
272
307
(MonadSTM m , GetTip l , HasLedgerTables l ) =>
0 commit comments