Skip to content

Commit 94bccd9

Browse files
Merge branch 'master' into fix-hls-graph-build
2 parents f840607 + 2fa5994 commit 94bccd9

File tree

17 files changed

+341
-93
lines changed

17 files changed

+341
-93
lines changed

Diff for: ghcide/ghcide.cabal

+4
Original file line numberDiff line numberDiff line change
@@ -74,6 +74,7 @@ library
7474
parallel,
7575
prettyprinter-ansi-terminal,
7676
prettyprinter,
77+
random,
7778
regex-tdfa >= 1.3.1.0,
7879
retrie,
7980
rope-utf16-splay,
@@ -392,11 +393,13 @@ test-suite ghcide-tests
392393
process,
393394
QuickCheck,
394395
quickcheck-instances,
396+
random,
395397
rope-utf16-splay,
396398
regex-tdfa ^>= 1.3.1,
397399
safe,
398400
safe-exceptions,
399401
shake,
402+
sqlite-simple,
400403
stm,
401404
stm-containers,
402405
hls-graph,
@@ -421,6 +424,7 @@ test-suite ghcide-tests
421424
Experiments
422425
Experiments.Types
423426
Progress
427+
HieDbRetry
424428
default-extensions:
425429
BangPatterns
426430
DeriveFunctor

Diff for: ghcide/session-loader/Development/IDE/Session.hs

+107-11
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE RankNTypes #-}
12
{-# LANGUAGE TypeFamilies #-}
23

34
{-|
@@ -11,6 +12,8 @@ module Development.IDE.Session
1112
,setInitialDynFlags
1213
,getHieDbLoc
1314
,runWithDb
15+
,retryOnSqliteBusy
16+
,retryOnException
1417
) where
1518

1619
-- Unfortunately, we cannot use loadSession with ghc-lib since hie-bios uses
@@ -41,7 +44,7 @@ import qualified Data.Text as T
4144
import Data.Time.Clock
4245
import Data.Version
4346
import Development.IDE.Core.RuleTypes
44-
import Development.IDE.Core.Shake
47+
import Development.IDE.Core.Shake hiding (withHieDb)
4548
import qualified Development.IDE.GHC.Compat as Compat
4649
import Development.IDE.GHC.Compat.Core hiding (Target,
4750
TargetFile, TargetModule,
@@ -82,9 +85,12 @@ import Data.Foldable (for_)
8285
import qualified Data.HashSet as Set
8386
import Database.SQLite.Simple
8487
import Development.IDE.Core.Tracing (withTrace)
88+
import Development.IDE.Types.Shake (WithHieDb)
8589
import HieDb.Create
8690
import HieDb.Types
8791
import HieDb.Utils
92+
import System.Random (RandomGen)
93+
import qualified System.Random as Random
8894

8995
-- | Bump this version number when making changes to the format of the data stored in hiedb
9096
hiedbDataVersion :: String
@@ -165,28 +171,118 @@ setInitialDynFlags logger rootDir SessionLoadingOptions{..} = do
165171
mapM_ setUnsafeGlobalDynFlags dynFlags
166172
pure libdir
167173

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+
168250
-- | Wraps `withHieDb` to provide a database connection for reading, and a `HieWriterChan` for
169251
-- writing. Actions are picked off one by one from the `HieWriterChan` and executed in serial
170252
-- by a worker thread using a dedicated database connection.
171253
-- 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 ()
173255
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
174259
-- 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+
177265
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+
179273
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)
182277
where
183-
writerThread db chan = do
278+
writerThread :: WithHieDb -> IndexQueue -> IO ()
279+
writerThread withHieDbRetryable chan = do
184280
-- 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
187283
forever $ do
188284
k <- atomically $ readTQueue chan
189-
k db
285+
k withHieDbRetryable
190286
`Safe.catch` \e@SQLError{} -> do
191287
logDebug logger $ T.pack $ "SQLite error in worker, ignoring: " ++ show e
192288
`Safe.catchAny` \e -> do

Diff for: ghcide/src/Development/IDE/Core/Actions.hs

+10-13
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
{-# LANGUAGE TypeFamilies #-}
1+
{-# LANGUAGE RankNTypes #-}
2+
{-# LANGUAGE TypeFamilies #-}
23
module Development.IDE.Core.Actions
34
( getAtPoint
45
, getDefinition
@@ -83,24 +84,20 @@ usesE k = MaybeT . fmap sequence . mapM (useWithStaleFast k)
8384
-- | Goto Definition.
8485
getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
8586
getDefinition file pos = runMaybeT $ do
86-
ide <- ask
87+
ide@ShakeExtras{ withHieDb, hiedbWriter } <- ask
8788
opts <- liftIO $ getIdeOptionsIO ide
8889
(HAR _ hf _ _ _, mapping) <- useE GetHieAst file
8990
(ImportMap imports, _) <- useE GetImportMap file
9091
!pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
91-
hiedb <- lift $ asks hiedb
92-
dbWriter <- lift $ asks hiedbWriter
93-
toCurrentLocations mapping <$> AtPoint.gotoDefinition hiedb (lookupMod dbWriter) opts imports hf pos'
92+
toCurrentLocations mapping <$> AtPoint.gotoDefinition withHieDb (lookupMod hiedbWriter) opts imports hf pos'
9493

9594
getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
9695
getTypeDefinition file pos = runMaybeT $ do
97-
ide <- ask
96+
ide@ShakeExtras{ withHieDb, hiedbWriter } <- ask
9897
opts <- liftIO $ getIdeOptionsIO ide
9998
(hf, mapping) <- useE GetHieAst file
10099
!pos' <- MaybeT (return $ fromCurrentPosition mapping pos)
101-
hiedb <- lift $ asks hiedb
102-
dbWriter <- lift $ asks hiedbWriter
103-
toCurrentLocations mapping <$> AtPoint.gotoTypeDefinition hiedb (lookupMod dbWriter) opts hf pos'
100+
toCurrentLocations mapping <$> AtPoint.gotoTypeDefinition withHieDb (lookupMod hiedbWriter) opts hf pos'
104101

105102
highlightAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe [DocumentHighlight])
106103
highlightAtPoint file pos = runMaybeT $ do
@@ -112,13 +109,13 @@ highlightAtPoint file pos = runMaybeT $ do
112109
-- Refs are not an IDE action, so it is OK to be slow and (more) accurate
113110
refsAtPoint :: NormalizedFilePath -> Position -> Action [Location]
114111
refsAtPoint file pos = do
115-
ShakeExtras{hiedb} <- getShakeExtras
112+
ShakeExtras{withHieDb} <- getShakeExtras
116113
fs <- HM.keys <$> getFilesOfInterestUntracked
117114
asts <- HM.fromList . mapMaybe sequence . zip fs <$> usesWithStale GetHieAst fs
118-
AtPoint.referencesAtPoint hiedb file pos (AtPoint.FOIReferences asts)
115+
AtPoint.referencesAtPoint withHieDb file pos (AtPoint.FOIReferences asts)
119116

120117
workspaceSymbols :: T.Text -> IdeAction (Maybe [SymbolInformation])
121118
workspaceSymbols query = runMaybeT $ do
122-
hiedb <- lift $ asks hiedb
123-
res <- liftIO $ HieDb.searchDef hiedb $ T.unpack query
119+
ShakeExtras{withHieDb} <- ask
120+
res <- liftIO $ withHieDb (\hieDb -> HieDb.searchDef hieDb $ T.unpack query)
124121
pure $ mapMaybe AtPoint.defRowToSymbolInfo res

Diff for: ghcide/src/Development/IDE/Core/Compile.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -521,7 +521,7 @@ indexHieFile se mod_summary srcPath !hash hf = do
521521
-- hiedb doesn't use the Haskell src, so we clear it to avoid unnecessarily keeping it around
522522
let !hf' = hf{hie_hs_src = mempty}
523523
modifyTVar' indexPending $ HashMap.insert srcPath hash
524-
writeTQueue indexQueue $ \db -> do
524+
writeTQueue indexQueue $ \withHieDb -> do
525525
-- We are now in the worker thread
526526
-- Check if a newer index of this file has been scheduled, and if so skip this one
527527
newerScheduled <- atomically $ do
@@ -532,7 +532,7 @@ indexHieFile se mod_summary srcPath !hash hf = do
532532
Just pendingHash -> pendingHash /= hash
533533
unless newerScheduled $ do
534534
pre optProgressStyle
535-
addRefsFromLoaded db targetPath (RealFile $ fromNormalizedFilePath srcPath) hash hf'
535+
withHieDb (\db -> HieDb.addRefsFromLoaded db targetPath (HieDb.RealFile $ fromNormalizedFilePath srcPath) hash hf')
536536
post
537537
where
538538
mod_location = ms_location mod_summary

Diff for: ghcide/src/Development/IDE/Core/FileStore.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -294,7 +294,7 @@ setSomethingModified state keys reason = do
294294
fail "setSomethingModified can't be called on this type of VFSHandle"
295295
-- Update database to remove any files that might have been renamed/deleted
296296
atomically $ do
297-
writeTQueue (indexQueue $ hiedbWriter $ shakeExtras state) deleteMissingRealFiles
297+
writeTQueue (indexQueue $ hiedbWriter $ shakeExtras state) (\withHieDb -> withHieDb deleteMissingRealFiles)
298298
modifyTVar' (dirtyKeys $ shakeExtras state) $ \x ->
299299
foldl' (flip HSet.insert) x keys
300300
void $ restartShakeSession (shakeExtras state) reason []

Diff for: ghcide/src/Development/IDE/Core/Rules.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -596,9 +596,9 @@ persistentDocMapRule = addPersistentRule GetDocMap $ \_ -> pure $ Just (DKMap me
596596

597597
readHieFileForSrcFromDisk :: NormalizedFilePath -> MaybeT IdeAction Compat.HieFile
598598
readHieFileForSrcFromDisk file = do
599-
db <- asks hiedb
599+
ShakeExtras{withHieDb} <- ask
600600
log <- asks $ L.logDebug . logger
601-
row <- MaybeT $ liftIO $ HieDb.lookupHieFileFromSource db $ fromNormalizedFilePath file
601+
row <- MaybeT $ liftIO $ withHieDb (\hieDb -> HieDb.lookupHieFileFromSource hieDb $ fromNormalizedFilePath file)
602602
let hie_loc = HieDb.hieModuleHieFile row
603603
liftIO $ log $ "LOADING HIE FILE :" <> T.pack (show file)
604604
exceptToMaybeT $ readHieFileFromDisk hie_loc
@@ -770,13 +770,13 @@ getModIfaceFromDiskAndIndexRule =
770770
-- doesn't need early cutoff since all its dependencies already have it
771771
defineNoDiagnostics $ \GetModIfaceFromDiskAndIndex f -> do
772772
x <- use_ GetModIfaceFromDisk f
773-
se@ShakeExtras{hiedb} <- getShakeExtras
773+
se@ShakeExtras{withHieDb} <- getShakeExtras
774774

775775
-- GetModIfaceFromDisk should have written a `.hie` file, must check if it matches version in db
776776
let ms = hirModSummary x
777777
hie_loc = Compat.ml_hie_file $ ms_location ms
778778
hash <- liftIO $ Util.getFileHash hie_loc
779-
mrow <- liftIO $ HieDb.lookupHieFileFromSource hiedb (fromNormalizedFilePath f)
779+
mrow <- liftIO $ withHieDb (\hieDb -> HieDb.lookupHieFileFromSource hieDb (fromNormalizedFilePath f))
780780
hie_loc' <- liftIO $ traverse (makeAbsolute . HieDb.hieModuleHieFile) mrow
781781
case mrow of
782782
Just row

Diff for: ghcide/src/Development/IDE/Core/Service.hs

+5-4
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,8 @@ import qualified Language.LSP.Types as LSP
3030

3131
import Control.Monad
3232
import Development.IDE.Core.Shake
33-
import System.Environment (lookupEnv)
33+
import Development.IDE.Types.Shake (WithHieDb)
34+
import System.Environment (lookupEnv)
3435

3536

3637
------------------------------------------------------------
@@ -44,10 +45,10 @@ initialise :: Config
4445
-> Debouncer LSP.NormalizedUri
4546
-> IdeOptions
4647
-> VFSHandle
47-
-> HieDb
48+
-> WithHieDb
4849
-> IndexQueue
4950
-> IO IdeState
50-
initialise defaultConfig mainRule lspEnv logger debouncer options vfs hiedb hiedbChan = do
51+
initialise defaultConfig mainRule lspEnv logger debouncer options vfs withHieDb hiedbChan = do
5152
shakeProfiling <- do
5253
let fromConf = optShakeProfiling options
5354
fromEnv <- lookupEnv "GHCIDE_BUILD_PROFILING"
@@ -60,7 +61,7 @@ initialise defaultConfig mainRule lspEnv logger debouncer options vfs hiedb hied
6061
shakeProfiling
6162
(optReportProgress options)
6263
(optTesting options)
63-
hiedb
64+
withHieDb
6465
hiedbChan
6566
vfs
6667
(optShakeOptions options)

Diff for: ghcide/src/Development/IDE/Core/Shake.hs

+7-5
Original file line numberDiff line numberDiff line change
@@ -182,7 +182,9 @@ data HieDbWriter
182182
}
183183

184184
-- | Actions to queue up on the index worker thread
185-
type IndexQueue = TQueue (HieDb -> IO ())
185+
-- The inner `(HieDb -> IO ()) -> IO ()` wraps `HieDb -> IO ()`
186+
-- with (currently) retry functionality
187+
type IndexQueue = TQueue (((HieDb -> IO ()) -> IO ()) -> IO ())
186188

187189
-- information we stash inside the shakeExtra field
188190
data ShakeExtras = ShakeExtras
@@ -219,7 +221,7 @@ data ShakeExtras = ShakeExtras
219221
-- | A work queue for actions added via 'runInShakeSession'
220222
,actionQueue :: ActionQueue
221223
,clientCapabilities :: ClientCapabilities
222-
, hiedb :: HieDb -- ^ Use only to read.
224+
, withHieDb :: WithHieDb -- ^ Use only to read.
223225
, hiedbWriter :: HieDbWriter -- ^ use to write
224226
, persistentKeys :: TVar (HMap.HashMap Key GetStalePersistent)
225227
-- ^ Registery for functions that compute/get "stale" results for the rule
@@ -499,14 +501,14 @@ shakeOpen :: Maybe (LSP.LanguageContextEnv Config)
499501
-> Maybe FilePath
500502
-> IdeReportProgress
501503
-> IdeTesting
502-
-> HieDb
504+
-> WithHieDb
503505
-> IndexQueue
504506
-> VFSHandle
505507
-> ShakeOptions
506508
-> Rules ()
507509
-> IO IdeState
508510
shakeOpen lspEnv defaultConfig logger debouncer
509-
shakeProfileDir (IdeReportProgress reportProgress) ideTesting@(IdeTesting testing) hiedb indexQueue vfs opts rules = mdo
511+
shakeProfileDir (IdeReportProgress reportProgress) ideTesting@(IdeTesting testing) withHieDb indexQueue vfs opts rules = mdo
510512

511513
us <- mkSplitUniqSupply 'r'
512514
ideNc <- newIORef (initNameCache us knownKeyNames)
@@ -528,7 +530,7 @@ shakeOpen lspEnv defaultConfig logger debouncer
528530
-- lazily initialize the exports map with the contents of the hiedb
529531
_ <- async $ do
530532
logDebug logger "Initializing exports map from hiedb"
531-
em <- createExportsMapHieDb hiedb
533+
em <- createExportsMapHieDb withHieDb
532534
atomically $ modifyTVar' exportsMap (<> em)
533535
logDebug logger $ "Done initializing exports map from hiedb (" <> pack(show (ExportsMap.size em)) <> ")"
534536

0 commit comments

Comments
 (0)