Skip to content

Commit 00d08b8

Browse files
fendorjneirapepeiborramergify[bot]
authored
Avoid unnecessary Target canonicalisation in Session setup (#2359)
* Add test-case for projects that use symbolic links In particular, this test checks whether modules that are actually symbolic lins can be found by ghcide. This is known to be broken, as Session.hs canonicalises Targets, e.g. saves the location of the symbolic link. When we later try to load that module, we can't find it, as it won't be part of the known targets since it is not canonicalized. * Dont canonicalise Targets during session setup Canonicalising Targets makes it harder later to actually find the targets during import analysis, as ghcide only looks for modules in the import paths and checks for existence in the known target Map. However, import analysis doesn't canonicalise target candidates, thus the lookup in the known target Map will always fail. We no longer canonicalise Targets, so import analysis will succeed loading modules that are actually symbolic links. * Prefer makeAbsolute over canonicalizePath * Use makeAbsolute to read HIE files from disk * Restore repeated builds the ghcide build fails for win and ghc-8.8 with segfaults Co-authored-by: Javier Neira <[email protected]> Co-authored-by: Pepe Iborra <[email protected]> Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent d0ccc2f commit 00d08b8

File tree

10 files changed

+46
-15
lines changed

10 files changed

+46
-15
lines changed

.github/workflows/test.yml

+2-1
Original file line numberDiff line numberDiff line change
@@ -139,8 +139,9 @@ jobs:
139139
sed -i.bak -e 's/Paths_haskell_language_server/Paths_hls/g' \
140140
src/**/*.hs exe/*.hs
141141
142+
# repeating builds to workaround segfaults in windows and ghc-8.8.4
142143
- name: Build
143-
run: cabal build
144+
run: cabal build || cabal build || cabal build
144145

145146
- name: Set test options
146147
run: |

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-
locs <- mapM (fmap toNormalizedFilePath' . canonicalizePath) 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-
nf <- toNormalizedFilePath' <$> canonicalizePath 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/Core/Rules.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ import Ide.Plugin.Config
138138
import qualified Language.LSP.Server as LSP
139139
import Language.LSP.Types (SMethod (SCustomMethod))
140140
import Language.LSP.VFS
141-
import System.Directory (canonicalizePath, makeAbsolute)
141+
import System.Directory (makeAbsolute)
142142
import Data.Default (def, Default)
143143
import Ide.Plugin.Properties (HasProperty,
144144
KeyNameProxy,
@@ -769,7 +769,7 @@ getModIfaceFromDiskAndIndexRule =
769769
hie_loc = Compat.ml_hie_file $ ms_location ms
770770
hash <- liftIO $ Util.getFileHash hie_loc
771771
mrow <- liftIO $ HieDb.lookupHieFileFromSource hiedb (fromNormalizedFilePath f)
772-
hie_loc' <- liftIO $ traverse (canonicalizePath . HieDb.hieModuleHieFile) mrow
772+
hie_loc' <- liftIO $ traverse (makeAbsolute . HieDb.hieModuleHieFile) mrow
773773
case mrow of
774774
Just row
775775
| hash == HieDb.modInfoHash (HieDb.hieModInfo row)

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

ghcide/test/data/symlink/hie.yaml

+10
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
2+
cradle:
3+
direct:
4+
arguments:
5+
- -i
6+
- -isrc
7+
- -iother_loc/
8+
- other_loc/Sym.hs
9+
- src/Foo.hs
10+
- -Wall

ghcide/test/data/symlink/other_loc/.gitkeep

Whitespace-only changes.
+4
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
module Sym where
2+
3+
foo :: String
4+
foo = ""

ghcide/test/data/symlink/src/Foo.hs

+4
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
module Foo where
2+
3+
import Sym
4+

ghcide/test/exe/Main.hs

+13-1
Original file line numberDiff line numberDiff line change
@@ -164,6 +164,7 @@ main = do
164164
, pluginParsedResultTests
165165
, preprocessorTests
166166
, thTests
167+
, symlinkTests
167168
, safeTests
168169
, unitTests
169170
, haddockTests
@@ -4051,14 +4052,25 @@ thTests =
40514052
expectDiagnostics [ ( cPath, [(DsWarning, (3, 0), "Top-level binding with no type signature: a :: A")] ) ]
40524053
]
40534054

4055+
-- | Tests for projects that use symbolic links one way or another
4056+
symlinkTests :: TestTree
4057+
symlinkTests =
4058+
testGroup "Projects using Symlinks"
4059+
[ testCase "Module is symlinked" $ runWithExtraFiles "symlink" $ \dir -> do
4060+
liftIO $ createFileLink (dir </> "some_loc" </> "Sym.hs") (dir </> "other_loc" </> "Sym.hs")
4061+
let fooPath = dir </> "src" </> "Foo.hs"
4062+
_ <- openDoc fooPath "haskell"
4063+
expectDiagnosticsWithTags [("src" </> "Foo.hs", [(DsWarning, (2, 0), "The import of 'Sym' is redundant", Just DtUnnecessary)])]
4064+
pure ()
4065+
]
4066+
40544067
-- | Test that all modules have linkables
40554068
thLoadingTest :: TestTree
40564069
thLoadingTest = testCase "Loading linkables" $ runWithExtraFiles "THLoading" $ \dir -> do
40574070
let thb = dir </> "THB.hs"
40584071
_ <- openDoc thb "haskell"
40594072
expectNoMoreDiagnostics 1
40604073

4061-
40624074
-- | test that TH is reevaluated on typecheck
40634075
thReloadingTest :: Bool -> TestTree
40644076
thReloadingTest unboxed = testCase name $ runWithExtraFiles dir $ \dir -> do

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)