1
+ {-# LANGUAGE RankNTypes #-}
1
2
{-# LANGUAGE TypeFamilies #-}
2
3
3
4
{-|
@@ -11,6 +12,8 @@ module Development.IDE.Session
11
12
,setInitialDynFlags
12
13
,getHieDbLoc
13
14
,runWithDb
15
+ ,retryOnSqliteBusy
16
+ ,retryOnException
14
17
) where
15
18
16
19
-- Unfortunately, we cannot use loadSession with ghc-lib since hie-bios uses
@@ -41,7 +44,7 @@ import qualified Data.Text as T
41
44
import Data.Time.Clock
42
45
import Data.Version
43
46
import Development.IDE.Core.RuleTypes
44
- import Development.IDE.Core.Shake
47
+ import Development.IDE.Core.Shake hiding ( withHieDb )
45
48
import qualified Development.IDE.GHC.Compat as Compat
46
49
import Development.IDE.GHC.Compat.Core hiding (Target ,
47
50
TargetFile , TargetModule ,
@@ -82,9 +85,12 @@ import Data.Foldable (for_)
82
85
import qualified Data.HashSet as Set
83
86
import Database.SQLite.Simple
84
87
import Development.IDE.Core.Tracing (withTrace )
88
+ import Development.IDE.Types.Shake (WithHieDb )
85
89
import HieDb.Create
86
90
import HieDb.Types
87
91
import HieDb.Utils
92
+ import System.Random (RandomGen )
93
+ import qualified System.Random as Random
88
94
89
95
-- | Bump this version number when making changes to the format of the data stored in hiedb
90
96
hiedbDataVersion :: String
@@ -165,28 +171,118 @@ setInitialDynFlags logger rootDir SessionLoadingOptions{..} = do
165
171
mapM_ setUnsafeGlobalDynFlags dynFlags
166
172
pure libdir
167
173
174
+ -- | If the action throws exception that satisfies predicate then we sleep for
175
+ -- a duration determined by the random exponential backoff formula,
176
+ -- `uniformRandom(0, min (maxDelay, (baseDelay * 2) ^ retryAttempt))`, and try
177
+ -- the action again for a maximum of `maxRetryCount` times.
178
+ -- `MonadIO`, `MonadCatch` are used as constraints because there are a few
179
+ -- HieDb functions that don't return IO values.
180
+ retryOnException
181
+ :: (MonadIO m , MonadCatch m , RandomGen g , Exception e )
182
+ => (e -> Maybe e ) -- ^ only retry on exception if this predicate returns Just
183
+ -> Logger
184
+ -> Int -- ^ maximum backoff delay in microseconds
185
+ -> Int -- ^ base backoff delay in microseconds
186
+ -> Int -- ^ maximum number of times to retry
187
+ -> g -- ^ random number generator
188
+ -> m a -- ^ action that may throw exception
189
+ -> m a
190
+ retryOnException exceptionPred logger maxDelay ! baseDelay ! maxRetryCount rng action = do
191
+ result <- tryJust exceptionPred action
192
+ case result of
193
+ Left e
194
+ | maxRetryCount > 0 -> do
195
+ -- multiply by 2 because baseDelay is midpoint of uniform range
196
+ let newBaseDelay = min maxDelay (baseDelay * 2 )
197
+ let (delay, newRng) = Random. randomR (0 , newBaseDelay) rng
198
+ let newMaxRetryCount = maxRetryCount - 1
199
+ liftIO $ do
200
+ logWarning logger $ " Retrying - " <> makeLogMsgComponentsText (Right delay) newMaxRetryCount e
201
+ threadDelay delay
202
+ retryOnException exceptionPred logger maxDelay newBaseDelay newMaxRetryCount newRng action
203
+
204
+ | otherwise -> do
205
+ liftIO $ do
206
+ logWarning logger $ " Retries exhausted - " <> makeLogMsgComponentsText (Left baseDelay) maxRetryCount e
207
+ throwIO e
208
+
209
+ Right b -> pure b
210
+ where
211
+ -- e.g. delay: 1010102, maximumDelay: 12010, maxRetryCount: 9, exception: SQLError { ... }
212
+ makeLogMsgComponentsText delay newMaxRetryCount e =
213
+ let
214
+ logMsgComponents =
215
+ [ either
216
+ ((" base delay: " <> ) . T. pack . show )
217
+ ((" delay: " <> ) . T. pack . show )
218
+ delay
219
+ , " maximumDelay: " <> T. pack (show maxDelay)
220
+ , " maxRetryCount: " <> T. pack (show newMaxRetryCount)
221
+ , " exception: " <> T. pack (show e)]
222
+ in
223
+ T. intercalate " , " logMsgComponents
224
+
225
+ -- | in microseconds
226
+ oneSecond :: Int
227
+ oneSecond = 1000000
228
+
229
+ -- | in microseconds
230
+ oneMillisecond :: Int
231
+ oneMillisecond = 1000
232
+
233
+ -- | default maximum number of times to retry hiedb call
234
+ maxRetryCount :: Int
235
+ maxRetryCount = 10
236
+
237
+ retryOnSqliteBusy :: (MonadIO m , MonadCatch m , RandomGen g )
238
+ => Logger -> g -> m a -> m a
239
+ retryOnSqliteBusy logger rng action =
240
+ let isErrorBusy e
241
+ | SQLError { sqlError = ErrorBusy } <- e = Just e
242
+ | otherwise = Nothing
243
+ in
244
+ retryOnException isErrorBusy logger oneSecond oneMillisecond maxRetryCount rng action
245
+
246
+ makeWithHieDbRetryable :: RandomGen g => Logger -> g -> HieDb -> WithHieDb
247
+ makeWithHieDbRetryable logger rng hieDb f =
248
+ retryOnSqliteBusy logger rng (f hieDb)
249
+
168
250
-- | Wraps `withHieDb` to provide a database connection for reading, and a `HieWriterChan` for
169
251
-- writing. Actions are picked off one by one from the `HieWriterChan` and executed in serial
170
252
-- by a worker thread using a dedicated database connection.
171
253
-- This is done in order to serialize writes to the database, or else SQLite becomes unhappy
172
- runWithDb :: Logger -> FilePath -> (HieDb -> IndexQueue -> IO () ) -> IO ()
254
+ runWithDb :: Logger -> FilePath -> (WithHieDb -> IndexQueue -> IO () ) -> IO ()
173
255
runWithDb logger fp k = do
256
+ -- use non-deterministic seed because maybe multiple HLS start at same time
257
+ -- and send bursts of requests
258
+ rng <- Random. newStdGen
174
259
-- Delete the database if it has an incompatible schema version
175
- withHieDb fp (const $ pure () )
176
- `Safe.catch` \ IncompatibleSchemaVersion {} -> removeFile fp
260
+ retryOnSqliteBusy
261
+ logger
262
+ rng
263
+ (withHieDb fp (const $ pure () ) `Safe.catch` \ IncompatibleSchemaVersion {} -> removeFile fp)
264
+
177
265
withHieDb fp $ \ writedb -> do
178
- initConn writedb
266
+ -- the type signature is necessary to avoid concretizing the tyvar
267
+ -- e.g. `withWriteDbRetrable initConn` without type signature will
268
+ -- instantiate tyvar `a` to `()`
269
+ let withWriteDbRetryable :: WithHieDb
270
+ withWriteDbRetryable = makeWithHieDbRetryable logger rng writedb
271
+ withWriteDbRetryable initConn
272
+
179
273
chan <- newTQueueIO
180
- withAsync (writerThread writedb chan) $ \ _ -> do
181
- withHieDb fp (flip k chan)
274
+
275
+ withAsync (writerThread withWriteDbRetryable chan) $ \ _ -> do
276
+ withHieDb fp (\ readDb -> k (makeWithHieDbRetryable logger rng readDb) chan)
182
277
where
183
- writerThread db chan = do
278
+ writerThread :: WithHieDb -> IndexQueue -> IO ()
279
+ writerThread withHieDbRetryable chan = do
184
280
-- Clear the index of any files that might have been deleted since the last run
185
- deleteMissingRealFiles db
186
- _ <- garbageCollectTypeNames db
281
+ _ <- withHieDbRetryable deleteMissingRealFiles
282
+ _ <- withHieDbRetryable garbageCollectTypeNames
187
283
forever $ do
188
284
k <- atomically $ readTQueue chan
189
- k db
285
+ k withHieDbRetryable
190
286
`Safe.catch` \ e@ SQLError {} -> do
191
287
logDebug logger $ T. pack $ " SQLite error in worker, ignoring: " ++ show e
192
288
`Safe.catchAny` \ e -> do
0 commit comments