Skip to content

Commit e6ceb69

Browse files
Boot files (#2377)
* Prefer source modules when combining HPTs * add a direct import into a module's boot module * disable boot fake import dependency * Add a test Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 08d6aaa commit e6ceb69

File tree

11 files changed

+79
-23
lines changed

11 files changed

+79
-23
lines changed

ghcide/src/Development/IDE/Core/Compile.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -106,7 +106,7 @@ import Data.Map (Map)
106106
import Data.Tuple.Extra (dupe)
107107
import Data.Unique as Unique
108108
import Development.IDE.Core.Tracing (withTrace)
109-
import Development.IDE.GHC.Compat.Util (emptyUDFM, plusUDFM)
109+
import Development.IDE.GHC.Compat.Util (emptyUDFM, plusUDFM_C)
110110
import qualified Language.LSP.Server as LSP
111111
import qualified Language.LSP.Types as LSP
112112
import Unsafe.Coerce
@@ -702,11 +702,15 @@ mergeEnvs env extraModSummaries extraMods envs = do
702702
(\fc (im, ifr) -> Compat.extendInstalledModuleEnv fc im ifr) prevFinderCache
703703
$ zip ims ifrs
704704
return $ loadModulesHome extraMods $ env{
705-
hsc_HPT = foldMapBy plusUDFM emptyUDFM hsc_HPT envs,
705+
hsc_HPT = foldMapBy mergeUDFM emptyUDFM hsc_HPT envs,
706706
hsc_FC = newFinderCache,
707707
hsc_mod_graph = mkModuleGraph $ extraModSummaries ++ nubOrdOn ms_mod (concatMap (mgModSummaries . hsc_mod_graph) envs)
708708
}
709709
where
710+
mergeUDFM = plusUDFM_C combineModules
711+
combineModules a b
712+
| HsSrcFile <- mi_hsc_src (hm_iface a) = a
713+
| otherwise = b
710714
-- required because 'FinderCache':
711715
-- 1) doesn't have a 'Monoid' instance,
712716
-- 2) is abstract and doesn't export constructors

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 17 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -348,7 +348,22 @@ getLocatedImportsRule =
348348
Left diags -> pure (diags, Just (modName, Nothing))
349349
Right (FileImport path) -> pure ([], Just (modName, Just path))
350350
Right PackageImport -> pure ([], Nothing)
351-
let moduleImports = catMaybes imports'
351+
352+
{- IS THIS REALLY NEEDED? DOESNT SEEM SO
353+
354+
-- does this module have an hs-boot file? If so add a direct dependency
355+
let bootPath = toNormalizedFilePath' $ fromNormalizedFilePath file <.> "hs-boot"
356+
boot <- use GetFileExists bootPath
357+
bootArtifact <- if boot == Just True
358+
then do
359+
let modName = ms_mod_name ms
360+
loc <- liftIO $ mkHomeModLocation dflags modName (fromNormalizedFilePath bootPath)
361+
return $ Just (noLoc modName, Just (ArtifactsLocation bootPath (Just loc) True))
362+
else pure Nothing
363+
-}
364+
let bootArtifact = Nothing
365+
366+
let moduleImports = catMaybes $ bootArtifact : imports'
352367
pure (concat diags, Just moduleImports)
353368

354369
type RawDepM a = StateT (RawDependencyInformation, IntMap ArtifactsLocation) Action a
@@ -374,7 +389,7 @@ rawDependencyInformation fs = do
374389

375390
go :: NormalizedFilePath -- ^ Current module being processed
376391
-> Maybe ModSummary -- ^ ModSummary of the module
377-
-> StateT (RawDependencyInformation, IntMap ArtifactsLocation) Action FilePathId
392+
-> RawDepM FilePathId
378393
go f msum = do
379394
-- First check to see if we have already processed the FilePath
380395
-- If we have, just return its Id but don't update any of the state.

ghcide/src/Development/IDE/GHC/Compat/Util.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,7 @@ module Development.IDE.GHC.Compat.Util (
6262
-- * UniqDFM
6363
emptyUDFM,
6464
plusUDFM,
65+
plusUDFM_C,
6566
-- * String Buffer
6667
StringBuffer(..),
6768
hGetStringBuffer,

ghcide/test/data/boot2/A.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
module A where
2+
3+
-- E source imports B
4+
-- In interface file see source module dependencies: B {-# SOURCE #-}
5+
import E
6+
-- C imports B
7+
-- In interface file see source module dependencies: B
8+
import C
9+
10+
-- Instance for B only available from B.hi not B.hi-boot, so tests we load
11+
-- that.
12+
main = print B

ghcide/test/data/boot2/B.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
module B where
2+
3+
import D
4+
5+
data B = B
6+
7+
instance Show B where
8+
show B = "B"

ghcide/test/data/boot2/B.hs-boot

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
module B where
2+
3+
data B = B

ghcide/test/data/boot2/C.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
module C where
2+
3+
import B

ghcide/test/data/boot2/D.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
module D where
2+
3+
import {-# SOURCE #-} B

ghcide/test/data/boot2/E.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
module E(B(B)) where
2+
3+
import {-# SOURCE #-} B

ghcide/test/data/boot2/hie.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
cradle: {direct: {arguments: ["A.hs", "B.hs-boot", "B.hs", "C.hs", "D.hs", "E.hs"]}}

ghcide/test/exe/Main.hs

Lines changed: 22 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -5277,25 +5277,28 @@ ifaceTests = testGroup "Interface loading tests"
52775277
]
52785278

52795279
bootTests :: TestTree
5280-
bootTests = testCase "boot-def-test" $ runWithExtraFiles "boot" $ \dir -> do
5281-
let cPath = dir </> "C.hs"
5282-
cSource <- liftIO $ readFileUtf8 cPath
5283-
5284-
-- Dirty the cache
5285-
liftIO $ runInDir dir $ do
5286-
cDoc <- createDoc cPath "haskell" cSource
5287-
_ <- getHover cDoc $ Position 4 3
5288-
~() <- skipManyTill anyMessage $ satisfyMaybe $ \case
5289-
FromServerMess (SCustomMethod "ghcide/reference/ready") (NotMess NotificationMessage{_params = fp}) -> do
5290-
A.Success fp' <- pure $ fromJSON fp
5291-
if equalFilePath fp' cPath then pure () else Nothing
5292-
_ -> Nothing
5293-
closeDoc cDoc
5294-
5295-
cdoc <- createDoc cPath "haskell" cSource
5296-
locs <- getDefinitions cdoc (Position 7 4)
5297-
let floc = mkR 9 0 9 1
5298-
checkDefs locs (pure [floc])
5280+
bootTests = testGroup "boot"
5281+
[ testCase "boot-def-test" $ runWithExtraFiles "boot" $ \dir -> do
5282+
let cPath = dir </> "C.hs"
5283+
cSource <- liftIO $ readFileUtf8 cPath
5284+
-- Dirty the cache
5285+
liftIO $ runInDir dir $ do
5286+
cDoc <- createDoc cPath "haskell" cSource
5287+
_ <- getHover cDoc $ Position 4 3
5288+
~() <- skipManyTill anyMessage $ satisfyMaybe $ \case
5289+
FromServerMess (SCustomMethod "ghcide/reference/ready") (NotMess NotificationMessage{_params = fp}) -> do
5290+
A.Success fp' <- pure $ fromJSON fp
5291+
if equalFilePath fp' cPath then pure () else Nothing
5292+
_ -> Nothing
5293+
closeDoc cDoc
5294+
cdoc <- createDoc cPath "haskell" cSource
5295+
locs <- getDefinitions cdoc (Position 7 4)
5296+
let floc = mkR 9 0 9 1
5297+
checkDefs locs (pure [floc])
5298+
, testCase "graph with boot modules" $ runWithExtraFiles "boot2" $ \dir -> do
5299+
_ <- openDoc (dir </> "A.hs") "haskell"
5300+
expectNoMoreDiagnostics 2
5301+
]
52995302

53005303
-- | test that TH reevaluates across interfaces
53015304
ifaceTHTest :: TestTree

0 commit comments

Comments
 (0)