@@ -7,21 +7,19 @@ The logic for setting up a ghcide session by tapping into hie-bios.
77module Development.IDE.Session
88 (SessionLoadingOptions (.. )
99 ,CacheDirs (.. )
10- ,loadSession
1110 ,loadSessionWithOptions
1211 ,setInitialDynFlags
1312 ,getHieDbLoc
14- ,runWithDb
1513 ,retryOnSqliteBusy
1614 ,retryOnException
1715 ,Log (.. )
16+ ,runWithDb
1817 ) where
1918
2019-- Unfortunately, we cannot use loadSession with ghc-lib since hie-bios uses
2120-- the real GHC library and the types are incompatible. Furthermore, when
2221-- building with ghc-lib we need to make this Haskell agnostic, so no hie-bios!
2322
24- import Control.Concurrent.Async
2523import Control.Concurrent.Strict
2624import Control.Exception.Safe as Safe
2725import Control.Monad
@@ -100,14 +98,19 @@ import Control.Concurrent.STM.TQueue
10098import Control.DeepSeq
10199import Control.Exception (evaluate )
102100import Control.Monad.IO.Unlift (MonadUnliftIO )
101+ import Control.Monad.Trans.Cont (ContT (ContT , runContT ))
103102import Data.Foldable (for_ )
104103import Data.HashMap.Strict (HashMap )
105104import Data.HashSet (HashSet )
106105import qualified Data.HashSet as Set
107106import Database.SQLite.Simple
108107import Development.IDE.Core.Tracing (withTrace )
108+ import Development.IDE.Core.WorkerThread (awaitRunInThread ,
109+ withWorkerQueue )
109110import Development.IDE.Session.Diagnostics (renderCradleError )
110- import Development.IDE.Types.Shake (WithHieDb , toNoFileKey )
111+ import Development.IDE.Types.Shake (WithHieDb ,
112+ WithHieDbShield (.. ),
113+ toNoFileKey )
111114import HieDb.Create
112115import HieDb.Types
113116import HieDb.Utils
@@ -375,8 +378,10 @@ makeWithHieDbRetryable recorder rng hieDb f =
375378-- writing. Actions are picked off one by one from the `HieWriterChan` and executed in serial
376379-- by a worker thread using a dedicated database connection.
377380-- This is done in order to serialize writes to the database, or else SQLite becomes unhappy
378- runWithDb :: Recorder (WithPriority Log ) -> FilePath -> (WithHieDb -> IndexQueue -> IO () ) -> IO ()
379- runWithDb recorder fp k = do
381+ --
382+ -- Also see Note [Serializing runs in separate thread]
383+ runWithDb :: Recorder (WithPriority Log ) -> FilePath -> ContT () IO (WithHieDbShield , IndexQueue )
384+ runWithDb recorder fp = ContT $ \ k -> do
380385 -- use non-deterministic seed because maybe multiple HLS start at same time
381386 -- and send bursts of requests
382387 rng <- Random. newStdGen
@@ -394,18 +399,15 @@ runWithDb recorder fp k = do
394399 withWriteDbRetryable = makeWithHieDbRetryable recorder rng writedb
395400 withWriteDbRetryable initConn
396401
397- chan <- newTQueueIO
398402
399- withAsync (writerThread withWriteDbRetryable chan) $ \ _ -> do
400- withHieDb fp (\ readDb -> k (makeWithHieDbRetryable recorder rng readDb) chan)
403+ -- Clear the index of any files that might have been deleted since the last run
404+ _ <- withWriteDbRetryable deleteMissingRealFiles
405+ _ <- withWriteDbRetryable garbageCollectTypeNames
406+
407+ runContT (withWorkerQueue (writer withWriteDbRetryable)) $ \ chan ->
408+ withHieDb fp (\ readDb -> k (WithHieDbShield $ makeWithHieDbRetryable recorder rng readDb, chan))
401409 where
402- writerThread :: WithHieDb -> IndexQueue -> IO ()
403- writerThread withHieDbRetryable chan = do
404- -- Clear the index of any files that might have been deleted since the last run
405- _ <- withHieDbRetryable deleteMissingRealFiles
406- _ <- withHieDbRetryable garbageCollectTypeNames
407- forever $ do
408- l <- atomically $ readTQueue chan
410+ writer withHieDbRetryable l = do
409411 -- TODO: probably should let exceptions be caught/logged/handled by top level handler
410412 l withHieDbRetryable
411413 `Safe.catch` \ e@ SQLError {} -> do
@@ -435,11 +437,9 @@ getHieDbLoc dir = do
435437-- This is the key function which implements multi-component support. All
436438-- components mapping to the same hie.yaml file are mapped to the same
437439-- HscEnv which is updated as new components are discovered.
438- loadSession :: Recorder (WithPriority Log ) -> FilePath -> IO (Action IdeGhcSession )
439- loadSession recorder = loadSessionWithOptions recorder def
440440
441- loadSessionWithOptions :: Recorder (WithPriority Log ) -> SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession )
442- loadSessionWithOptions recorder SessionLoadingOptions {.. } rootDir = do
441+ loadSessionWithOptions :: Recorder (WithPriority Log ) -> SessionLoadingOptions -> FilePath -> TQueue ( IO () ) -> IO (Action IdeGhcSession )
442+ loadSessionWithOptions recorder SessionLoadingOptions {.. } rootDir que = do
443443 let toAbsolutePath = toAbsolute rootDir -- see Note [Root Directory]
444444 cradle_files <- newIORef []
445445 -- Mapping from hie.yaml file to HscEnv, one per hie.yaml file
@@ -464,9 +464,6 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir = do
464464 let res' = toAbsolutePath <$> res
465465 return $ normalise <$> res'
466466
467- dummyAs <- async $ return (error " Uninitialised" )
468- runningCradle <- newVar dummyAs :: IO (Var (Async (IdeResult HscEnvEq ,[FilePath ])))
469-
470467 return $ do
471468 clientConfig <- getClientConfigAction
472469 extras@ ShakeExtras {restartShakeSession, ideNc, knownTargetsVar, lspEnv
@@ -739,12 +736,8 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir = do
739736 return (([renderPackageSetupException file e], Nothing ), maybe [] pure hieYaml)
740737
741738 returnWithVersion $ \ file -> do
742- opts <- join $ mask_ $ modifyVar runningCradle $ \ as -> do
743- -- If the cradle is not finished, then wait for it to finish.
744- void $ wait as
745- asyncRes <- async $ getOptions file
746- return (asyncRes, wait asyncRes)
747- pure opts
739+ -- see Note [Serializing runs in separate thread]
740+ awaitRunInThread que $ getOptions file
748741
749742-- | Run the specific cradle on a specific FilePath via hie-bios.
750743-- This then builds dependencies or whatever based on the cradle, gets the
0 commit comments