@@ -25,7 +25,7 @@ import Control.Concurrent.Async
25
25
import Control.Concurrent.Strict
26
26
import Control.Exception.Safe as Safe
27
27
import Control.Monad
28
- import Control.Monad.Extra
28
+ import Control.Monad.Extra as Extra
29
29
import Control.Monad.IO.Class
30
30
import qualified Crypto.Hash.SHA1 as H
31
31
import Data.Aeson hiding (Error )
@@ -69,6 +69,7 @@ import Development.IDE.Types.Location
69
69
import Development.IDE.Types.Options
70
70
import GHC.Check
71
71
import qualified HIE.Bios as HieBios
72
+ import qualified HIE.Bios.Cradle as HieBios
72
73
import HIE.Bios.Environment hiding (getCacheDir )
73
74
import HIE.Bios.Types hiding (Log )
74
75
import qualified HIE.Bios.Types as HieBios
@@ -79,6 +80,8 @@ import Ide.Logger (Pretty (pretty),
79
80
nest ,
80
81
toCologActionWithPrio ,
81
82
vcat , viaShow , (<+>) )
83
+ import Ide.Types (SessionLoadingPreferenceConfig (.. ),
84
+ sessionLoading )
82
85
import Language.LSP.Protocol.Message
83
86
import Language.LSP.Server
84
87
import System.Directory
@@ -147,6 +150,7 @@ data Log
147
150
| LogNoneCradleFound FilePath
148
151
| LogNewComponentCache ! (([FileDiagnostic ], Maybe HscEnvEq ), DependencyInfo )
149
152
| LogHieBios HieBios. Log
153
+ | LogSessionLoadingChanged
150
154
deriving instance Show Log
151
155
152
156
instance Pretty Log where
@@ -217,6 +221,8 @@ instance Pretty Log where
217
221
LogNewComponentCache componentCache ->
218
222
" New component cache HscEnvEq:" <+> viaShow componentCache
219
223
LogHieBios msg -> pretty msg
224
+ LogSessionLoadingChanged ->
225
+ " Session Loading config changed, reloading the full session."
220
226
221
227
-- | Bump this version number when making changes to the format of the data stored in hiedb
222
228
hiedbDataVersion :: String
@@ -447,6 +453,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
447
453
filesMap <- newVar HM. empty :: IO (Var FilesMap )
448
454
-- Version of the mappings above
449
455
version <- newVar 0
456
+ biosSessionLoadingVar <- newVar Nothing :: IO (Var (Maybe SessionLoadingPreferenceConfig ))
450
457
let returnWithVersion fun = IdeGhcSession fun <$> liftIO (readVar version)
451
458
-- This caches the mapping from Mod.hs -> hie.yaml
452
459
cradleLoc <- liftIO $ memoIO $ \ v -> do
@@ -461,6 +468,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
461
468
runningCradle <- newVar dummyAs :: IO (Var (Async (IdeResult HscEnvEq ,[FilePath ])))
462
469
463
470
return $ do
471
+ clientConfig <- getClientConfigAction
464
472
extras@ ShakeExtras {restartShakeSession, ideNc, knownTargetsVar, lspEnv
465
473
} <- getShakeExtras
466
474
let invalidateShakeCache :: IO ()
@@ -651,7 +659,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
651
659
withTrace " Load cradle" $ \ addTag -> do
652
660
addTag " file" lfp
653
661
old_files <- readIORef cradle_files
654
- res <- cradleToOptsAndLibDir recorder cradle cfp old_files
662
+ res <- cradleToOptsAndLibDir recorder (sessionLoading clientConfig) cradle cfp old_files
655
663
addTag " result" (show res)
656
664
return res
657
665
@@ -679,11 +687,38 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
679
687
void $ modifyVar' filesMap $ HM. insert ncfp hieYaml
680
688
return (res, maybe [] pure hieYaml ++ concatMap cradleErrorDependencies err)
681
689
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
+
682
708
-- This caches the mapping from hie.yaml + Mod.hs -> [String]
683
709
-- Returns the Ghc session and the cradle dependencies
684
710
let sessionOpts :: (Maybe FilePath , FilePath )
685
711
-> IO (IdeResult HscEnvEq , [FilePath ])
686
712
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
+
687
722
v <- Map. findWithDefault HM. empty hieYaml <$> readVar fileToFlags
688
723
cfp <- makeAbsolute file
689
724
case HM. lookup (toNormalizedFilePath' cfp) v of
@@ -694,6 +729,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
694
729
-- If the dependencies are out of date then clear both caches and start
695
730
-- again.
696
731
modifyVar_ fileToFlags (const (return Map. empty))
732
+ modifyVar_ filesMap (const (return HM. empty))
697
733
-- Keep the same name cache
698
734
modifyVar_ hscEnvs (return . Map. adjust (const [] ) hieYaml )
699
735
consultCradle hieYaml cfp
@@ -713,7 +749,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
713
749
return (([renderPackageSetupException file e], Nothing ), maybe [] pure hieYaml)
714
750
715
751
returnWithVersion $ \ file -> do
716
- opts <- liftIO $ join $ mask_ $ modifyVar runningCradle $ \ as -> do
752
+ opts <- join $ mask_ $ modifyVar runningCradle $ \ as -> do
717
753
-- If the cradle is not finished, then wait for it to finish.
718
754
void $ wait as
719
755
asyncRes <- async $ getOptions file
@@ -723,14 +759,14 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
723
759
-- | Run the specific cradle on a specific FilePath via hie-bios.
724
760
-- This then builds dependencies or whatever based on the cradle, gets the
725
761
-- 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 ]
727
763
-> IO (Either [CradleError ] (ComponentOptions , FilePath ))
728
- cradleToOptsAndLibDir recorder cradle file old_files = do
764
+ cradleToOptsAndLibDir recorder loadConfig cradle file old_fps = do
729
765
-- let noneCradleFoundMessage :: FilePath -> T.Text
730
766
-- noneCradleFoundMessage f = T.pack $ "none cradle found for " <> f <> ", ignoring the file"
731
767
-- Start off by getting the session options
732
768
logWith recorder Debug $ LogCradle cradle
733
- cradleRes <- HieBios. getCompilerOptions file old_files cradle
769
+ cradleRes <- HieBios. getCompilerOptions file loadStyle cradle
734
770
case cradleRes of
735
771
CradleSuccess r -> do
736
772
-- Now get the GHC lib dir
@@ -748,6 +784,11 @@ cradleToOptsAndLibDir recorder cradle file old_files = do
748
784
logWith recorder Info $ LogNoneCradleFound file
749
785
return (Left [] )
750
786
787
+ where
788
+ loadStyle = case loadConfig of
789
+ PreferSingleComponentLoading -> LoadFile
790
+ PreferMultiComponentLoading -> LoadWithContext old_fps
791
+
751
792
#if MIN_VERSION_ghc(9,3,0)
752
793
emptyHscEnv :: NameCache -> FilePath -> IO HscEnv
753
794
#else
@@ -1093,7 +1134,7 @@ setOptions cfp (ComponentOptions theOpts compRoot _) dflags = do
1093
1134
-- component to be created. In case the cradle doesn't list all the targets for
1094
1135
-- the component, in which case things will be horribly broken anyway.
1095
1136
--
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
1097
1138
-- file, we assume the file is part of that component. This is useful
1098
1139
-- for bare GHC sessions, such as many of the ones used in the testsuite
1099
1140
--
0 commit comments