Skip to content

Commit cc76fcc

Browse files
committed
Prefer makeAbsolute over canonicalizePath
1 parent 38d3fcc commit cc76fcc

File tree

3 files changed

+11
-11
lines changed

3 files changed

+11
-11
lines changed

ghcide/session-loader/Development/IDE/Session.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -462,7 +462,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
462462
-> IO (IdeResult HscEnvEq, [FilePath])
463463
sessionOpts (hieYaml, file) = do
464464
v <- fromMaybe HM.empty . Map.lookup hieYaml <$> readVar fileToFlags
465-
cfp <- canonicalizePath file
465+
cfp <- makeAbsolute file
466466
case HM.lookup (toNormalizedFilePath' cfp) v of
467467
Just (opts, old_di) -> do
468468
deps_ok <- checkDependencyInfo old_di
@@ -483,7 +483,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
483483
-- before attempting to do so.
484484
let getOptions :: FilePath -> IO (IdeResult HscEnvEq, [FilePath])
485485
getOptions file = do
486-
ncfp <- toNormalizedFilePath' <$> canonicalizePath file
486+
ncfp <- toNormalizedFilePath' <$> makeAbsolute file
487487
cachedHieYamlLocation <- HM.lookup ncfp <$> readVar filesMap
488488
hieYaml <- cradleLoc file
489489
sessionOpts (join cachedHieYamlLocation <|> hieYaml, file) `Safe.catch` \e ->
@@ -553,11 +553,11 @@ fromTargetId is exts (GHC.TargetModule mod) env dep = do
553553
, i <- is
554554
, boot <- ["", "-boot"]
555555
]
556-
let locs = map toNormalizedFilePath' fps
556+
locs <- mapM (fmap toNormalizedFilePath' . makeAbsolute) fps
557557
return [TargetDetails (TargetModule mod) env dep locs]
558558
-- For a 'TargetFile' we consider all the possible module names
559559
fromTargetId _ _ (GHC.TargetFile f _) env deps = do
560-
let nf = toNormalizedFilePath' f
560+
nf <- toNormalizedFilePath' <$> makeAbsolute f
561561
return [TargetDetails (TargetFile nf) env deps [nf]]
562562

563563
toFlagsMap :: TargetDetails -> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]

ghcide/src/Development/IDE/Types/HscEnvEq.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ import Development.IDE.GHC.Util (lookupPackageConfig)
2929
import Development.IDE.Graph.Classes
3030
import Development.IDE.Types.Exports (ExportsMap, createExportsMap)
3131
import OpenTelemetry.Eventlog (withSpan)
32-
import System.Directory (canonicalizePath)
32+
import System.Directory (makeAbsolute)
3333
import System.FilePath
3434

3535
-- | An 'HscEnv' with equality. Two values are considered equal
@@ -58,9 +58,9 @@ newHscEnvEq cradlePath hscEnv0 deps = do
5858
let relativeToCradle = (takeDirectory cradlePath </>)
5959
hscEnv = removeImportPaths hscEnv0
6060

61-
-- Canonicalize import paths since we also canonicalize targets
61+
-- Make Absolute since targets are also absolute
6262
importPathsCanon <-
63-
mapM canonicalizePath $ relativeToCradle <$> importPaths (hsc_dflags hscEnv0)
63+
mapM makeAbsolute $ relativeToCradle <$> importPaths (hsc_dflags hscEnv0)
6464

6565
newHscEnvEqWithImportPaths (Just $ Set.fromList importPathsCanon) hscEnv deps
6666

plugins/hls-module-name-plugin/src/Ide/Plugin/ModuleName.hs

+4-4
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ import Data.Char (isLower)
2323
import qualified Data.HashMap.Strict as HashMap
2424
import Data.List (intercalate, isPrefixOf, minimumBy)
2525
import Data.Maybe (maybeToList)
26+
import Data.Ord (comparing)
2627
import Data.String (IsString)
2728
import qualified Data.Text as T
2829
import Development.IDE (GetParsedModule (GetParsedModule),
@@ -41,10 +42,9 @@ import Language.LSP.Types hiding
4142
SemanticTokenRelative (length),
4243
SemanticTokensEdit (_start))
4344
import Language.LSP.VFS (virtualFileText)
44-
import System.Directory (canonicalizePath)
45+
import System.Directory (makeAbsolute)
4546
import System.FilePath (dropExtension, splitDirectories,
4647
takeFileName)
47-
import Data.Ord (comparing)
4848

4949
-- |Plugin descriptor
5050
descriptor :: PluginId -> PluginDescriptor IdeState
@@ -121,8 +121,8 @@ pathModuleNames state normFilePath filePath
121121
| otherwise = do
122122
session <- runAction "ModuleName.ghcSession" state $ use_ GhcSession normFilePath
123123
srcPaths <- evalGhcEnv (hscEnvWithImportPaths session) $ importPaths <$> getSessionDynFlags
124-
paths <- mapM canonicalizePath srcPaths
125-
mdlPath <- canonicalizePath filePath
124+
paths <- mapM makeAbsolute srcPaths
125+
mdlPath <- makeAbsolute filePath
126126
let prefixes = filter (`isPrefixOf` mdlPath) paths
127127
pure (map (moduleNameFrom mdlPath) prefixes)
128128
where

0 commit comments

Comments
 (0)