@@ -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 )
@@ -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 (SessionLoadingPreferenceConfig (.. ),
84+ sessionLoading )
8285import Language.LSP.Protocol.Message
8386import Language.LSP.Server
8487import System.Directory
@@ -147,6 +150,7 @@ data Log
147150 | LogNoneCradleFound FilePath
148151 | LogNewComponentCache ! (([FileDiagnostic ], Maybe HscEnvEq ), DependencyInfo )
149152 | LogHieBios HieBios. Log
153+ | LogSessionLoadingChanged
150154deriving instance Show Log
151155
152156instance Pretty Log where
@@ -217,6 +221,8 @@ instance Pretty Log where
217221 LogNewComponentCache componentCache ->
218222 " New component cache HscEnvEq:" <+> viaShow componentCache
219223 LogHieBios msg -> pretty msg
224+ LogSessionLoadingChanged ->
225+ " Session Loading config changed, reloading the full session."
220226
221227-- | Bump this version number when making changes to the format of the data stored in hiedb
222228hiedbDataVersion :: String
@@ -447,6 +453,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
447453 filesMap <- newVar HM. empty :: IO (Var FilesMap )
448454 -- Version of the mappings above
449455 version <- newVar 0
456+ biosSessionLoadingVar <- newVar Nothing :: IO (Var (Maybe SessionLoadingPreferenceConfig ))
450457 let returnWithVersion fun = IdeGhcSession fun <$> liftIO (readVar version)
451458 -- This caches the mapping from Mod.hs -> hie.yaml
452459 cradleLoc <- liftIO $ memoIO $ \ v -> do
@@ -461,6 +468,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
461468 runningCradle <- newVar dummyAs :: IO (Var (Async (IdeResult HscEnvEq ,[FilePath ])))
462469
463470 return $ do
471+ clientConfig <- getClientConfigAction
464472 extras@ ShakeExtras {restartShakeSession, ideNc, knownTargetsVar, lspEnv
465473 } <- getShakeExtras
466474 let invalidateShakeCache :: IO ()
@@ -651,7 +659,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
651659 withTrace " Load cradle" $ \ addTag -> do
652660 addTag " file" lfp
653661 old_files <- readIORef cradle_files
654- res <- cradleToOptsAndLibDir recorder cradle cfp old_files
662+ res <- cradleToOptsAndLibDir recorder (sessionLoading clientConfig) cradle cfp old_files
655663 addTag " result" (show res)
656664 return res
657665
@@ -679,11 +687,38 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
679687 void $ modifyVar' filesMap $ HM. insert ncfp hieYaml
680688 return (res, maybe [] pure hieYaml ++ concatMap cradleErrorDependencies err)
681689
690+ let
691+ -- | We allow users to specify a loading strategy.
692+ -- Check whether this config was changed since the last time we have loaded
693+ -- a session.
694+ --
695+ -- If the loading configuration changed, we likely should restart the session
696+ -- in its entirety.
697+ didSessionLoadingPreferenceConfigChange :: IO Bool
698+ didSessionLoadingPreferenceConfigChange = do
699+ mLoadingConfig <- readVar biosSessionLoadingVar
700+ case mLoadingConfig of
701+ Nothing -> do
702+ writeVar biosSessionLoadingVar (Just (sessionLoading clientConfig))
703+ pure False
704+ Just loadingConfig -> do
705+ writeVar biosSessionLoadingVar (Just (sessionLoading clientConfig))
706+ pure (loadingConfig /= sessionLoading clientConfig)
707+
682708 -- This caches the mapping from hie.yaml + Mod.hs -> [String]
683709 -- Returns the Ghc session and the cradle dependencies
684710 let sessionOpts :: (Maybe FilePath , FilePath )
685711 -> IO (IdeResult HscEnvEq , [FilePath ])
686712 sessionOpts (hieYaml, file) = do
713+ Extra. whenM didSessionLoadingPreferenceConfigChange $ do
714+ logWith recorder Info LogSessionLoadingChanged
715+ -- If the dependencies are out of date then clear both caches and start
716+ -- again.
717+ modifyVar_ fileToFlags (const (return Map. empty))
718+ modifyVar_ filesMap (const (return HM. empty))
719+ -- Don't even keep the name cache, we start from scratch here!
720+ modifyVar_ hscEnvs (const (return Map. empty))
721+
687722 v <- Map. findWithDefault HM. empty hieYaml <$> readVar fileToFlags
688723 cfp <- makeAbsolute file
689724 case HM. lookup (toNormalizedFilePath' cfp) v of
@@ -694,6 +729,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
694729 -- If the dependencies are out of date then clear both caches and start
695730 -- again.
696731 modifyVar_ fileToFlags (const (return Map. empty))
732+ modifyVar_ filesMap (const (return HM. empty))
697733 -- Keep the same name cache
698734 modifyVar_ hscEnvs (return . Map. adjust (const [] ) hieYaml )
699735 consultCradle hieYaml cfp
@@ -713,7 +749,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
713749 return (([renderPackageSetupException file e], Nothing ), maybe [] pure hieYaml)
714750
715751 returnWithVersion $ \ file -> do
716- opts <- liftIO $ join $ mask_ $ modifyVar runningCradle $ \ as -> do
752+ opts <- join $ mask_ $ modifyVar runningCradle $ \ as -> do
717753 -- If the cradle is not finished, then wait for it to finish.
718754 void $ wait as
719755 asyncRes <- async $ getOptions file
@@ -723,14 +759,14 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
723759-- | Run the specific cradle on a specific FilePath via hie-bios.
724760-- This then builds dependencies or whatever based on the cradle, gets the
725761-- GHC options/dynflags needed for the session and the GHC library directory
726- cradleToOptsAndLibDir :: Recorder (WithPriority Log ) -> Cradle Void -> FilePath -> [FilePath ]
762+ cradleToOptsAndLibDir :: Recorder (WithPriority Log ) -> SessionLoadingPreferenceConfig -> Cradle Void -> FilePath -> [FilePath ]
727763 -> IO (Either [CradleError ] (ComponentOptions , FilePath ))
728- cradleToOptsAndLibDir recorder cradle file old_files = do
764+ cradleToOptsAndLibDir recorder loadConfig cradle file old_fps = do
729765 -- let noneCradleFoundMessage :: FilePath -> T.Text
730766 -- noneCradleFoundMessage f = T.pack $ "none cradle found for " <> f <> ", ignoring the file"
731767 -- Start off by getting the session options
732768 logWith recorder Debug $ LogCradle cradle
733- cradleRes <- HieBios. getCompilerOptions file old_files cradle
769+ cradleRes <- HieBios. getCompilerOptions file loadStyle cradle
734770 case cradleRes of
735771 CradleSuccess r -> do
736772 -- Now get the GHC lib dir
@@ -748,6 +784,11 @@ cradleToOptsAndLibDir recorder cradle file old_files = do
748784 logWith recorder Info $ LogNoneCradleFound file
749785 return (Left [] )
750786
787+ where
788+ loadStyle = case loadConfig of
789+ PreferSingleComponentLoading -> LoadFile
790+ PreferMultiComponentLoading -> LoadWithContext old_fps
791+
751792#if MIN_VERSION_ghc(9,3,0)
752793emptyHscEnv :: NameCache -> FilePath -> IO HscEnv
753794#else
@@ -1093,7 +1134,7 @@ setOptions cfp (ComponentOptions theOpts compRoot _) dflags = do
10931134 -- component to be created. In case the cradle doesn't list all the targets for
10941135 -- the component, in which case things will be horribly broken anyway.
10951136 --
1096- -- When we have a single component that is caused to be loaded due to a
1137+ -- When we have a singleComponent that is caused to be loaded due to a
10971138 -- file, we assume the file is part of that component. This is useful
10981139 -- for bare GHC sessions, such as many of the ones used in the testsuite
10991140 --
0 commit comments