11{-# LANGUAGE ExistentialQuantification #-}
22{-# LANGUAGE RankNTypes #-}
33{-# LANGUAGE TypeFamilies #-}
4+ {-# LANGUAGE CPP #-}
45
56{-|
67The logic for setting up a ghcide session by tapping into hie-bios.
@@ -100,6 +101,10 @@ import HieDb.Types
100101import HieDb.Utils
101102import qualified System.Random as Random
102103import System.Random (RandomGen )
104+ import Control.Monad.IO.Unlift (MonadUnliftIO )
105+ import Debug.Trace
106+ import Control.Exception (evaluate )
107+ import Control.DeepSeq
103108
104109data Log
105110 = LogSettingInitialDynFlags
@@ -208,11 +213,13 @@ data SessionLoadingOptions = SessionLoadingOptions
208213 , getCacheDirs :: String -> [String ] -> IO CacheDirs
209214 -- | Return the GHC lib dir to use for the 'unsafeGlobalDynFlags'
210215 , getInitialGhcLibDir :: Recorder (WithPriority Log ) -> FilePath -> IO (Maybe LibDir )
216+ # if ! MIN_VERSION_ghc (9 ,3 ,0 )
211217 , fakeUid :: UnitId
212218 -- ^ unit id used to tag the internal component built by ghcide
213219 -- To reuse external interface files the unit ids must match,
214220 -- thus make sure to build them with `--this-unit-id` set to the
215221 -- same value as the ghcide fake uid
222+ # endif
216223 }
217224
218225instance Default SessionLoadingOptions where
@@ -221,7 +228,9 @@ instance Default SessionLoadingOptions where
221228 ,loadCradle = loadWithImplicitCradle
222229 ,getCacheDirs = getCacheDirsDefault
223230 ,getInitialGhcLibDir = getInitialGhcLibDirDefault
231+ #if !MIN_VERSION_ghc(9,3,0)
224232 ,fakeUid = Compat. toUnitId (Compat. stringToUnit " main" )
233+ #endif
225234 }
226235
227236-- | Find the cradle for a given 'hie.yaml' configuration.
@@ -494,7 +503,11 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
494503 new_deps' <- forM new_deps $ \ RawComponentInfo {.. } -> do
495504 -- Remove all inplace dependencies from package flags for
496505 -- components in this HscEnv
506+ #if MIN_VERSION_ghc(9,3,0)
507+ let (df2, uids) = (rawComponentDynFlags, [] )
508+ #else
497509 let (df2, uids) = removeInplacePackages fakeUid inplace rawComponentDynFlags
510+ #endif
498511 let prefix = show rawComponentUnitId
499512 -- See Note [Avoiding bad interface files]
500513 let hscComponents = sort $ map show uids
@@ -517,10 +530,14 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
517530 -- that I do not fully understand
518531 log Info $ LogMakingNewHscEnv inplace
519532 hscEnv <- emptyHscEnv ideNc libDir
520- newHscEnv <-
533+ ! newHscEnv <-
521534 -- Add the options for the current component to the HscEnv
522535 evalGhcEnv hscEnv $ do
523- _ <- setSessionDynFlags $ setHomeUnitId_ fakeUid df
536+ _ <- setSessionDynFlags
537+ #if !MIN_VERSION_ghc(9,3,0)
538+ $ setHomeUnitId_ fakeUid
539+ #endif
540+ df
524541 getSession
525542
526543 -- Modify the map so the hieYaml now maps to the newly created
@@ -718,7 +735,11 @@ cradleToOptsAndLibDir recorder cradle file = do
718735 logWith recorder Info $ LogNoneCradleFound file
719736 return (Left [] )
720737
738+ #if MIN_VERSION_ghc(9,3,0)
739+ emptyHscEnv :: NameCache -> FilePath -> IO HscEnv
740+ #else
721741emptyHscEnv :: IORef NameCache -> FilePath -> IO HscEnv
742+ #endif
722743emptyHscEnv nc libDir = do
723744 env <- runGhc (Just libDir) getSession
724745 initDynLinker env
@@ -757,7 +778,11 @@ toFlagsMap TargetDetails{..} =
757778 [ (l, (targetEnv, targetDepends)) | l <- targetLocations]
758779
759780
781+ #if MIN_VERSION_ghc(9,3,0)
782+ setNameCache :: NameCache -> HscEnv -> HscEnv
783+ #else
760784setNameCache :: IORef NameCache -> HscEnv -> HscEnv
785+ #endif
761786setNameCache nc hsc = hsc { hsc_NC = nc }
762787
763788-- | Create a mapping from FilePaths to HscEnvEqs
@@ -773,6 +798,11 @@ newComponentCache
773798newComponentCache recorder exts cradlePath cfp hsc_env uids ci = do
774799 let df = componentDynFlags ci
775800 hscEnv' <-
801+ #if MIN_VERSION_ghc(9,3,0)
802+ -- Set up a multi component session with the other units on GHC 9.4
803+ Compat. initUnits (map snd uids) (hscSetFlags df hsc_env)
804+ #elif MIN_VERSION_ghc(9,3,0)
805+ -- This initializes the units for GHC 9.2
776806 -- Add the options for the current component to the HscEnv
777807 -- We want to call `setSessionDynFlags` instead of `hscSetFlags`
778808 -- because `setSessionDynFlags` also initializes the package database,
@@ -782,14 +812,20 @@ newComponentCache recorder exts cradlePath cfp hsc_env uids ci = do
782812 evalGhcEnv hsc_env $ do
783813 _ <- setSessionDynFlags $ df
784814 getSession
815+ #else
816+ -- getOptions is enough to initialize units on GHC <9.2
817+ pure $ hscSetFlags df hsc_env { hsc_IC = (hsc_IC hsc_env) { ic_dflags = df } }
818+ #endif
785819
820+ traceM " got new hsc env"
786821
787822 let newFunc = maybe newHscEnvEqPreserveImportPaths newHscEnvEq cradlePath
788823 henv <- newFunc hscEnv' uids
789824 let targetEnv = ([] , Just henv)
790825 targetDepends = componentDependencyInfo ci
791826 res = (targetEnv, targetDepends)
792827 logWith recorder Debug $ LogNewComponentCache res
828+ evaluate $ liftRnf rwhnf $ componentTargets ci
793829
794830 let mk t = fromTargetId (importPaths df) exts (targetId t) targetEnv targetDepends
795831 ctargets <- concatMapM mk (componentTargets ci)
@@ -998,9 +1034,11 @@ setOptions (ComponentOptions theOpts compRoot _) dflags = do
9981034 -- initPackages parses the -package flags and
9991035 -- sets up the visibility for each component.
10001036 -- Throws if a -package flag cannot be satisfied.
1001- env <- hscSetFlags dflags'' <$> getSession
1002- final_env' <- liftIO $ wrapPackageSetupException $ Compat. initUnits env
1003- return (hsc_dflags final_env', targets)
1037+ -- This only works for GHC <9.2
1038+ -- For GHC >= 9.2, we need to modify the unit env in the hsc_dflags, which
1039+ -- is done later in newComponentCache
1040+ final_flags <- liftIO $ wrapPackageSetupException $ Compat. oldInitUnits dflags''
1041+ return (final_flags, targets)
10041042
10051043setIgnoreInterfacePragmas :: DynFlags -> DynFlags
10061044setIgnoreInterfacePragmas df =
0 commit comments