@@ -111,6 +111,7 @@ import Development.IDE.Types.Shake (WithHieDb, toNoFileKey)
111
111
import HieDb.Create
112
112
import HieDb.Types
113
113
import HieDb.Utils
114
+ import Ide.PluginUtils (toAbsolute )
114
115
import qualified System.Random as Random
115
116
import System.Random (RandomGen )
116
117
@@ -438,7 +439,8 @@ loadSession :: Recorder (WithPriority Log) -> FilePath -> IO (Action IdeGhcSessi
438
439
loadSession recorder = loadSessionWithOptions recorder def
439
440
440
441
loadSessionWithOptions :: Recorder (WithPriority Log ) -> SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession )
441
- loadSessionWithOptions recorder SessionLoadingOptions {.. } dir = do
442
+ loadSessionWithOptions recorder SessionLoadingOptions {.. } rootDir = do
443
+ let toAbsolutePath = toAbsolute rootDir -- see Note [Root Directory]
442
444
cradle_files <- newIORef []
443
445
-- Mapping from hie.yaml file to HscEnv, one per hie.yaml file
444
446
hscEnvs <- newVar Map. empty :: IO (Var HieMap )
@@ -459,7 +461,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
459
461
-- Sometimes we get C:, sometimes we get c:, and sometimes we get a relative path
460
462
-- try and normalise that
461
463
-- e.g. see https://github.com/haskell/ghcide/issues/126
462
- res' <- traverse makeAbsolute res
464
+ let res' = toAbsolutePath <$> res
463
465
return $ normalise <$> res'
464
466
465
467
dummyAs <- async $ return (error " Uninitialised" )
@@ -521,7 +523,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
521
523
packageSetup (hieYaml, cfp, opts, libDir) = do
522
524
-- Parse DynFlags for the newly discovered component
523
525
hscEnv <- emptyHscEnv ideNc libDir
524
- newTargetDfs <- evalGhcEnv hscEnv $ setOptions cfp opts (hsc_dflags hscEnv)
526
+ newTargetDfs <- evalGhcEnv hscEnv $ setOptions cfp opts (hsc_dflags hscEnv) rootDir
525
527
let deps = componentDependencies opts ++ maybeToList hieYaml
526
528
dep_info <- getDependencyInfo deps
527
529
-- Now lookup to see whether we are combining with an existing HscEnv
@@ -588,7 +590,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
588
590
-- HscEnv but set the active component accordingly
589
591
hscEnv <- emptyHscEnv ideNc _libDir
590
592
let new_cache = newComponentCache recorder optExtensions hieYaml _cfp hscEnv
591
- all_target_details <- new_cache old_deps new_deps
593
+ all_target_details <- new_cache old_deps new_deps rootDir
592
594
593
595
this_dep_info <- getDependencyInfo $ maybeToList hieYaml
594
596
let (all_targets, this_flags_map, this_options)
@@ -632,25 +634,20 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
632
634
633
635
let consultCradle :: Maybe FilePath -> FilePath -> IO (IdeResult HscEnvEq , [FilePath ])
634
636
consultCradle hieYaml cfp = do
635
- lfpLog <- flip makeRelative cfp <$> getCurrentDirectory
637
+ let lfpLog = makeRelative rootDir cfp
636
638
logWith recorder Info $ LogCradlePath lfpLog
637
-
638
639
when (isNothing hieYaml) $
639
640
logWith recorder Warning $ LogCradleNotFound lfpLog
640
-
641
- cradle <- loadCradle recorder hieYaml dir
642
- -- TODO: Why are we repeating the same command we have on line 646?
643
- lfp <- flip makeRelative cfp <$> getCurrentDirectory
644
-
641
+ cradle <- loadCradle recorder hieYaml rootDir
645
642
when optTesting $ mRunLspT lspEnv $
646
643
sendNotification (SMethod_CustomMethod (Proxy @ " ghcide/cradle/loaded" )) (toJSON cfp)
647
644
648
645
-- Display a user friendly progress message here: They probably don't know what a cradle is
649
646
let progMsg = " Setting up " <> T. pack (takeBaseName (cradleRootDir cradle))
650
- <> " (for " <> T. pack lfp <> " )"
647
+ <> " (for " <> T. pack lfpLog <> " )"
651
648
eopts <- mRunLspTCallback lspEnv (\ act -> withIndefiniteProgress progMsg Nothing NotCancellable (const act)) $
652
649
withTrace " Load cradle" $ \ addTag -> do
653
- addTag " file" lfp
650
+ addTag " file" lfpLog
654
651
old_files <- readIORef cradle_files
655
652
res <- cradleToOptsAndLibDir recorder (sessionLoading clientConfig) cradle cfp old_files
656
653
addTag " result" (show res)
@@ -713,7 +710,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
713
710
modifyVar_ hscEnvs (const (return Map. empty))
714
711
715
712
v <- Map. findWithDefault HM. empty hieYaml <$> readVar fileToFlags
716
- cfp <- makeAbsolute file
713
+ let cfp = toAbsolutePath file
717
714
case HM. lookup (toNormalizedFilePath' cfp) v of
718
715
Just (opts, old_di) -> do
719
716
deps_ok <- checkDependencyInfo old_di
@@ -735,7 +732,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
735
732
-- before attempting to do so.
736
733
let getOptions :: FilePath -> IO (IdeResult HscEnvEq , [FilePath ])
737
734
getOptions file = do
738
- ncfp <- toNormalizedFilePath' <$> makeAbsolute file
735
+ let ncfp = toNormalizedFilePath' (toAbsolutePath file)
739
736
cachedHieYamlLocation <- HM. lookup ncfp <$> readVar filesMap
740
737
hieYaml <- cradleLoc file
741
738
sessionOpts (join cachedHieYamlLocation <|> hieYaml, file) `Safe.catch` \ e ->
@@ -814,19 +811,20 @@ fromTargetId :: [FilePath] -- ^ import paths
814
811
-> TargetId
815
812
-> IdeResult HscEnvEq
816
813
-> DependencyInfo
814
+ -> FilePath -- ^ root dir, see Note [Root Directory]
817
815
-> IO [TargetDetails ]
818
816
-- For a target module we consider all the import paths
819
- fromTargetId is exts (GHC. TargetModule modName) env dep = do
817
+ fromTargetId is exts (GHC. TargetModule modName) env dep dir = do
820
818
let fps = [i </> moduleNameSlashes modName -<.> ext <> boot
821
819
| ext <- exts
822
820
, i <- is
823
821
, boot <- [" " , " -boot" ]
824
822
]
825
- locs <- mapM ( fmap toNormalizedFilePath' . makeAbsolute ) fps
823
+ let locs = fmap ( toNormalizedFilePath' . toAbsolute dir ) fps
826
824
return [TargetDetails (TargetModule modName) env dep locs]
827
825
-- For a 'TargetFile' we consider all the possible module names
828
- fromTargetId _ _ (GHC. TargetFile f _) env deps = do
829
- nf <- toNormalizedFilePath' <$> makeAbsolute f
826
+ fromTargetId _ _ (GHC. TargetFile f _) env deps dir = do
827
+ let nf = toNormalizedFilePath' $ toAbsolute dir f
830
828
let other
831
829
| " -boot" `isSuffixOf` f = toNormalizedFilePath' (L. dropEnd 5 $ fromNormalizedFilePath nf)
832
830
| otherwise = toNormalizedFilePath' (fromNormalizedFilePath nf ++ " -boot" )
@@ -915,8 +913,9 @@ newComponentCache
915
913
-> HscEnv -- ^ An empty HscEnv
916
914
-> [ComponentInfo ] -- ^ New components to be loaded
917
915
-> [ComponentInfo ] -- ^ old, already existing components
916
+ -> FilePath -- ^ root dir, see Note [Root Directory]
918
917
-> IO [ [TargetDetails ] ]
919
- newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis = do
918
+ newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis dir = do
920
919
let cis = Map. unionWith unionCIs (mkMap new_cis) (mkMap old_cis)
921
920
-- When we have multiple components with the same uid,
922
921
-- prefer the new one over the old.
@@ -961,7 +960,7 @@ newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis = do
961
960
962
961
forM (Map. elems cis) $ \ ci -> do
963
962
let df = componentDynFlags ci
964
- let createHscEnvEq = maybe newHscEnvEqPreserveImportPaths newHscEnvEq cradlePath
963
+ let createHscEnvEq = maybe newHscEnvEqPreserveImportPaths ( newHscEnvEq dir) cradlePath
965
964
thisEnv <- do
966
965
#if MIN_VERSION_ghc(9,3,0)
967
966
-- In GHC 9.4 we have multi component support, and we have initialised all the units
@@ -986,7 +985,7 @@ newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis = do
986
985
logWith recorder Debug $ LogNewComponentCache (targetEnv, targetDepends)
987
986
evaluate $ liftRnf rwhnf $ componentTargets ci
988
987
989
- let mk t = fromTargetId (importPaths df) exts (targetId t) targetEnv targetDepends
988
+ let mk t = fromTargetId (importPaths df) exts (targetId t) targetEnv targetDepends dir
990
989
ctargets <- concatMapM mk (componentTargets ci)
991
990
992
991
return (L. nubOrdOn targetTarget ctargets)
@@ -1171,8 +1170,13 @@ addUnit unit_str = liftEwM $ do
1171
1170
putCmdLineState (unit_str : units)
1172
1171
1173
1172
-- | Throws if package flags are unsatisfiable
1174
- setOptions :: GhcMonad m => NormalizedFilePath -> ComponentOptions -> DynFlags -> m (NonEmpty (DynFlags , [GHC. Target ]))
1175
- setOptions cfp (ComponentOptions theOpts compRoot _) dflags = do
1173
+ setOptions :: GhcMonad m
1174
+ => NormalizedFilePath
1175
+ -> ComponentOptions
1176
+ -> DynFlags
1177
+ -> FilePath -- ^ root dir, see Note [Root Directory]
1178
+ -> m (NonEmpty (DynFlags , [GHC. Target ]))
1179
+ setOptions cfp (ComponentOptions theOpts compRoot _) dflags rootDir = do
1176
1180
((theOpts',_errs,_warns),units) <- processCmdLineP unit_flags [] (map noLoc theOpts)
1177
1181
case NE. nonEmpty units of
1178
1182
Just us -> initMulti us
@@ -1195,7 +1199,7 @@ setOptions cfp (ComponentOptions theOpts compRoot _) dflags = do
1195
1199
--
1196
1200
-- If we don't end up with a target for the current file in the end, then
1197
1201
-- we will report it as an error for that file
1198
- abs_fp <- liftIO $ makeAbsolute (fromNormalizedFilePath cfp)
1202
+ let abs_fp = toAbsolute rootDir (fromNormalizedFilePath cfp)
1199
1203
let special_target = Compat. mkSimpleTarget df abs_fp
1200
1204
pure $ (df, special_target : targets) :| []
1201
1205
where
0 commit comments