@@ -25,7 +25,7 @@ import Control.Concurrent.Async
2525import Control.Concurrent.Strict
2626import Control.Exception.Safe as Safe
2727import Control.Monad
28- import Control.Monad.Extra
28+ import Control.Monad.Extra as Extra
2929import Control.Monad.IO.Class
3030import qualified Crypto.Hash.SHA1 as H
3131import Data.Aeson hiding (Error )
@@ -52,13 +52,13 @@ import Development.IDE.Core.RuleTypes
5252import Development.IDE.Core.Shake hiding (Log , Priority ,
5353 knownTargets , withHieDb )
5454import qualified Development.IDE.GHC.Compat as Compat
55- import qualified Development.IDE.GHC.Compat.Util as Compat
5655import Development.IDE.GHC.Compat.Core hiding (Target ,
5756 TargetFile , TargetModule ,
5857 Var , Warning , getOptions )
5958import qualified Development.IDE.GHC.Compat.Core as GHC
6059import Development.IDE.GHC.Compat.Env hiding (Logger )
6160import Development.IDE.GHC.Compat.Units (UnitId )
61+ import qualified Development.IDE.GHC.Compat.Util as Compat
6262import Development.IDE.GHC.Util
6363import Development.IDE.Graph (Action )
6464import Development.IDE.Session.VersionCheck
@@ -70,6 +70,7 @@ import Development.IDE.Types.Location
7070import Development.IDE.Types.Options
7171import GHC.Check
7272import qualified HIE.Bios as HieBios
73+ import qualified HIE.Bios.Cradle as HieBios
7374import HIE.Bios.Environment hiding (getCacheDir )
7475import HIE.Bios.Types hiding (Log )
7576import qualified HIE.Bios.Types as HieBios
@@ -80,6 +81,8 @@ import Ide.Logger (Pretty (pretty),
8081 nest ,
8182 toCologActionWithPrio ,
8283 vcat , viaShow , (<+>) )
84+ import Ide.Types (SessionLoadingPreferenceConfig (.. ),
85+ sessionLoading )
8386import Language.LSP.Protocol.Message
8487import Language.LSP.Server
8588import System.Directory
@@ -123,7 +126,8 @@ import GHC.Data.Bag
123126import GHC.Driver.Env (hsc_all_home_unit_ids )
124127import GHC.Driver.Errors.Types
125128import GHC.Driver.Make (checkHomeUnitsClosed )
126- import GHC.Types.Error (errMsgDiagnostic , singleMessage )
129+ import GHC.Types.Error (errMsgDiagnostic ,
130+ singleMessage )
127131import GHC.Unit.State
128132#endif
129133
@@ -149,6 +153,7 @@ data Log
149153 | LogNoneCradleFound FilePath
150154 | LogNewComponentCache ! (([FileDiagnostic ], Maybe HscEnvEq ), DependencyInfo )
151155 | LogHieBios HieBios. Log
156+ | LogSessionLoadingChanged
152157deriving instance Show Log
153158
154159instance Pretty Log where
@@ -219,6 +224,8 @@ instance Pretty Log where
219224 LogNewComponentCache componentCache ->
220225 " New component cache HscEnvEq:" <+> viaShow componentCache
221226 LogHieBios msg -> pretty msg
227+ LogSessionLoadingChanged ->
228+ " Session Loading config changed, reloading the full session."
222229
223230-- | Bump this version number when making changes to the format of the data stored in hiedb
224231hiedbDataVersion :: String
@@ -449,6 +456,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
449456 filesMap <- newVar HM. empty :: IO (Var FilesMap )
450457 -- Version of the mappings above
451458 version <- newVar 0
459+ biosSessionLoadingVar <- newVar Nothing :: IO (Var (Maybe SessionLoadingPreferenceConfig ))
452460 let returnWithVersion fun = IdeGhcSession fun <$> liftIO (readVar version)
453461 -- This caches the mapping from Mod.hs -> hie.yaml
454462 cradleLoc <- liftIO $ memoIO $ \ v -> do
@@ -463,6 +471,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
463471 runningCradle <- newVar dummyAs :: IO (Var (Async (IdeResult HscEnvEq ,[FilePath ])))
464472
465473 return $ do
474+ clientConfig <- getClientConfigAction
466475 extras@ ShakeExtras {restartShakeSession, ideNc, knownTargetsVar, lspEnv
467476 } <- getShakeExtras
468477 let invalidateShakeCache :: IO ()
@@ -653,7 +662,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
653662 withTrace " Load cradle" $ \ addTag -> do
654663 addTag " file" lfp
655664 old_files <- readIORef cradle_files
656- res <- cradleToOptsAndLibDir recorder cradle cfp old_files
665+ res <- cradleToOptsAndLibDir recorder (sessionLoading clientConfig) cradle cfp old_files
657666 addTag " result" (show res)
658667 return res
659668
@@ -681,11 +690,38 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
681690 void $ modifyVar' filesMap $ HM. insert ncfp hieYaml
682691 return (res, maybe [] pure hieYaml ++ concatMap cradleErrorDependencies err)
683692
693+ let
694+ -- | We allow users to specify a loading strategy.
695+ -- Check whether this config was changed since the last time we have loaded
696+ -- a session.
697+ --
698+ -- If the loading configuration changed, we likely should restart the session
699+ -- in its entirety.
700+ didSessionLoadingPreferenceConfigChange :: IO Bool
701+ didSessionLoadingPreferenceConfigChange = do
702+ mLoadingConfig <- readVar biosSessionLoadingVar
703+ case mLoadingConfig of
704+ Nothing -> do
705+ writeVar biosSessionLoadingVar (Just (sessionLoading clientConfig))
706+ pure False
707+ Just loadingConfig -> do
708+ writeVar biosSessionLoadingVar (Just (sessionLoading clientConfig))
709+ pure (loadingConfig /= sessionLoading clientConfig)
710+
684711 -- This caches the mapping from hie.yaml + Mod.hs -> [String]
685712 -- Returns the Ghc session and the cradle dependencies
686713 let sessionOpts :: (Maybe FilePath , FilePath )
687714 -> IO (IdeResult HscEnvEq , [FilePath ])
688715 sessionOpts (hieYaml, file) = do
716+ Extra. whenM didSessionLoadingPreferenceConfigChange $ do
717+ logWith recorder Info LogSessionLoadingChanged
718+ -- If the dependencies are out of date then clear both caches and start
719+ -- again.
720+ modifyVar_ fileToFlags (const (return Map. empty))
721+ modifyVar_ filesMap (const (return HM. empty))
722+ -- Don't even keep the name cache, we start from scratch here!
723+ modifyVar_ hscEnvs (const (return Map. empty))
724+
689725 v <- Map. findWithDefault HM. empty hieYaml <$> readVar fileToFlags
690726 cfp <- makeAbsolute file
691727 case HM. lookup (toNormalizedFilePath' cfp) v of
@@ -696,6 +732,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
696732 -- If the dependencies are out of date then clear both caches and start
697733 -- again.
698734 modifyVar_ fileToFlags (const (return Map. empty))
735+ modifyVar_ filesMap (const (return HM. empty))
699736 -- Keep the same name cache
700737 modifyVar_ hscEnvs (return . Map. adjust (const [] ) hieYaml )
701738 consultCradle hieYaml cfp
@@ -715,7 +752,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
715752 return (([renderPackageSetupException file e], Nothing ), maybe [] pure hieYaml)
716753
717754 returnWithVersion $ \ file -> do
718- opts <- liftIO $ join $ mask_ $ modifyVar runningCradle $ \ as -> do
755+ opts <- join $ mask_ $ modifyVar runningCradle $ \ as -> do
719756 -- If the cradle is not finished, then wait for it to finish.
720757 void $ wait as
721758 asyncRes <- async $ getOptions file
@@ -725,14 +762,14 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
725762-- | Run the specific cradle on a specific FilePath via hie-bios.
726763-- This then builds dependencies or whatever based on the cradle, gets the
727764-- GHC options/dynflags needed for the session and the GHC library directory
728- cradleToOptsAndLibDir :: Recorder (WithPriority Log ) -> Cradle Void -> FilePath -> [FilePath ]
765+ cradleToOptsAndLibDir :: Recorder (WithPriority Log ) -> SessionLoadingPreferenceConfig -> Cradle Void -> FilePath -> [FilePath ]
729766 -> IO (Either [CradleError ] (ComponentOptions , FilePath ))
730- cradleToOptsAndLibDir recorder cradle file old_files = do
767+ cradleToOptsAndLibDir recorder loadConfig cradle file old_fps = do
731768 -- let noneCradleFoundMessage :: FilePath -> T.Text
732769 -- noneCradleFoundMessage f = T.pack $ "none cradle found for " <> f <> ", ignoring the file"
733770 -- Start off by getting the session options
734771 logWith recorder Debug $ LogCradle cradle
735- cradleRes <- HieBios. getCompilerOptions file old_files cradle
772+ cradleRes <- HieBios. getCompilerOptions file loadStyle cradle
736773 case cradleRes of
737774 CradleSuccess r -> do
738775 -- Now get the GHC lib dir
@@ -750,6 +787,11 @@ cradleToOptsAndLibDir recorder cradle file old_files = do
750787 logWith recorder Info $ LogNoneCradleFound file
751788 return (Left [] )
752789
790+ where
791+ loadStyle = case loadConfig of
792+ PreferSingleComponentLoading -> LoadFile
793+ PreferMultiComponentLoading -> LoadWithContext old_fps
794+
753795#if MIN_VERSION_ghc(9,3,0)
754796emptyHscEnv :: NameCache -> FilePath -> IO HscEnv
755797#else
@@ -1150,7 +1192,7 @@ setOptions cfp (ComponentOptions theOpts compRoot _) dflags = do
11501192 -- component to be created. In case the cradle doesn't list all the targets for
11511193 -- the component, in which case things will be horribly broken anyway.
11521194 --
1153- -- When we have a single component that is caused to be loaded due to a
1195+ -- When we have a singleComponent that is caused to be loaded due to a
11541196 -- file, we assume the file is part of that component. This is useful
11551197 -- for bare GHC sessions, such as many of the ones used in the testsuite
11561198 --
0 commit comments