@@ -69,6 +69,7 @@ import Development.IDE.Types.Location
6969import Development.IDE.Types.Options
7070import GHC.Check
7171import qualified HIE.Bios as HieBios
72+ import qualified HIE.Bios.Cradle as HieBios
7273import HIE.Bios.Environment hiding (getCacheDir )
7374import HIE.Bios.Types hiding (Log )
7475import qualified HIE.Bios.Types as HieBios
@@ -79,6 +80,8 @@ import Ide.Logger (Pretty (pretty),
7980 nest ,
8081 toCologActionWithPrio ,
8182 vcat , viaShow , (<+>) )
83+ import Ide.Types (SessionLoadingConfig (.. ),
84+ sessionLoading )
8285import Language.LSP.Protocol.Message
8386import Language.LSP.Server
8487import System.Directory
@@ -127,6 +130,7 @@ import GHC.Unit.State
127130#endif
128131
129132import GHC.ResponseFile
133+ import qualified Control.Monad.Extra as Extra
130134
131135data Log
132136 = LogSettingInitialDynFlags
@@ -147,6 +151,7 @@ data Log
147151 | LogNoneCradleFound FilePath
148152 | LogNewComponentCache ! (([FileDiagnostic ], Maybe HscEnvEq ), DependencyInfo )
149153 | LogHieBios HieBios. Log
154+ | LogSessionLoadingChanged
150155deriving instance Show Log
151156
152157instance Pretty Log where
@@ -217,6 +222,8 @@ instance Pretty Log where
217222 LogNewComponentCache componentCache ->
218223 " New component cache HscEnvEq:" <+> viaShow componentCache
219224 LogHieBios msg -> pretty msg
225+ LogSessionLoadingChanged ->
226+ " Session Loading Config change, reload the full session."
220227
221228-- | Bump this version number when making changes to the format of the data stored in hiedb
222229hiedbDataVersion :: String
@@ -447,6 +454,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
447454 filesMap <- newVar HM. empty :: IO (Var FilesMap )
448455 -- Version of the mappings above
449456 version <- newVar 0
457+ biosSessionLoadingVar <- newVar Nothing :: IO (Var (Maybe SessionLoadingConfig ))
450458 let returnWithVersion fun = IdeGhcSession fun <$> liftIO (readVar version)
451459 -- This caches the mapping from Mod.hs -> hie.yaml
452460 cradleLoc <- liftIO $ memoIO $ \ v -> do
@@ -461,6 +469,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
461469 runningCradle <- newVar dummyAs :: IO (Var (Async (IdeResult HscEnvEq ,[FilePath ])))
462470
463471 return $ do
472+ clientConfig <- getClientConfigAction
464473 extras@ ShakeExtras {restartShakeSession, ideNc, knownTargetsVar, lspEnv
465474 } <- getShakeExtras
466475 let invalidateShakeCache :: IO ()
@@ -651,7 +660,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
651660 withTrace " Load cradle" $ \ addTag -> do
652661 addTag " file" lfp
653662 old_files <- readIORef cradle_files
654- res <- cradleToOptsAndLibDir recorder cradle cfp old_files
663+ res <- cradleToOptsAndLibDir recorder (sessionLoading clientConfig) cradle cfp old_files
655664 addTag " result" (show res)
656665 return res
657666
@@ -679,11 +688,38 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
679688 void $ modifyVar' filesMap $ HM. insert ncfp hieYaml
680689 return (res, maybe [] pure hieYaml ++ concatMap cradleErrorDependencies err)
681690
691+ let
692+ -- | We allow users to specify a loading strategy.
693+ -- Check whether this config was changed since the last time we have loaded
694+ -- a session.
695+ --
696+ -- If the loading configuration changed, we likely should restart the session
697+ -- in its entirety.
698+ didSessionLoadingConfigChange :: IO Bool
699+ didSessionLoadingConfigChange = do
700+ mLoadingConfig <- readVar biosSessionLoadingVar
701+ case mLoadingConfig of
702+ Nothing -> do
703+ writeVar biosSessionLoadingVar (Just (sessionLoading clientConfig))
704+ pure False
705+ Just loadingConfig -> do
706+ writeVar biosSessionLoadingVar (Just (sessionLoading clientConfig))
707+ pure (loadingConfig /= sessionLoading clientConfig)
708+
682709 -- This caches the mapping from hie.yaml + Mod.hs -> [String]
683710 -- Returns the Ghc session and the cradle dependencies
684711 let sessionOpts :: (Maybe FilePath , FilePath )
685712 -> IO (IdeResult HscEnvEq , [FilePath ])
686713 sessionOpts (hieYaml, file) = do
714+ Extra. whenM didSessionLoadingConfigChange $ do
715+ logWith recorder Info LogSessionLoadingChanged
716+ -- If the dependencies are out of date then clear both caches and start
717+ -- again.
718+ modifyVar_ fileToFlags (const (return Map. empty))
719+ modifyVar_ filesMap (const (return HM. empty))
720+ -- Don't even keep the name cache, we start from scratch here!
721+ modifyVar_ hscEnvs (const (return Map. empty))
722+
687723 v <- Map. findWithDefault HM. empty hieYaml <$> readVar fileToFlags
688724 cfp <- makeAbsolute file
689725 case HM. lookup (toNormalizedFilePath' cfp) v of
@@ -694,6 +730,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
694730 -- If the dependencies are out of date then clear both caches and start
695731 -- again.
696732 modifyVar_ fileToFlags (const (return Map. empty))
733+ modifyVar_ filesMap (const (return HM. empty))
697734 -- Keep the same name cache
698735 modifyVar_ hscEnvs (return . Map. adjust (const [] ) hieYaml )
699736 consultCradle hieYaml cfp
@@ -713,7 +750,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
713750 return (([renderPackageSetupException file e], Nothing ), maybe [] pure hieYaml)
714751
715752 returnWithVersion $ \ file -> do
716- opts <- liftIO $ join $ mask_ $ modifyVar runningCradle $ \ as -> do
753+ opts <- join $ mask_ $ modifyVar runningCradle $ \ as -> do
717754 -- If the cradle is not finished, then wait for it to finish.
718755 void $ wait as
719756 asyncRes <- async $ getOptions file
@@ -723,14 +760,14 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
723760-- | Run the specific cradle on a specific FilePath via hie-bios.
724761-- This then builds dependencies or whatever based on the cradle, gets the
725762-- GHC options/dynflags needed for the session and the GHC library directory
726- cradleToOptsAndLibDir :: Recorder (WithPriority Log ) -> Cradle Void -> FilePath -> [FilePath ]
763+ cradleToOptsAndLibDir :: Recorder (WithPriority Log ) -> SessionLoadingConfig -> Cradle Void -> FilePath -> [FilePath ]
727764 -> IO (Either [CradleError ] (ComponentOptions , FilePath ))
728- cradleToOptsAndLibDir recorder cradle file old_files = do
765+ cradleToOptsAndLibDir recorder loadConfig cradle file old_fps = do
729766 -- let noneCradleFoundMessage :: FilePath -> T.Text
730767 -- noneCradleFoundMessage f = T.pack $ "none cradle found for " <> f <> ", ignoring the file"
731768 -- Start off by getting the session options
732769 logWith recorder Debug $ LogCradle cradle
733- cradleRes <- HieBios. getCompilerOptions file old_files cradle
770+ cradleRes <- HieBios. getCompilerOptions file loadStyle cradle
734771 case cradleRes of
735772 CradleSuccess r -> do
736773 -- Now get the GHC lib dir
@@ -748,6 +785,11 @@ cradleToOptsAndLibDir recorder cradle file old_files = do
748785 logWith recorder Info $ LogNoneCradleFound file
749786 return (Left [] )
750787
788+ where
789+ loadStyle = case loadConfig of
790+ SessionLoadSingleComponent -> LoadFile
791+ SessionLoadMultipleComponents -> LoadWithContext old_fps
792+
751793#if MIN_VERSION_ghc(9,3,0)
752794emptyHscEnv :: NameCache -> FilePath -> IO HscEnv
753795#else
0 commit comments