Skip to content

Commit 7378ff1

Browse files
committed
Index dependency hie files
1 parent fdb1975 commit 7378ff1

File tree

10 files changed

+373
-99
lines changed

10 files changed

+373
-99
lines changed

cabal.project

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,11 @@ packages:
3737
./plugins/hls-refactor-plugin
3838
./plugins/hls-overloaded-record-dot-plugin
3939

40+
source-repository-package
41+
type:git
42+
location: https://github.com/nlander/HieDb.git
43+
tag: f10051a6dc1b809d5f40a45beab92205d1829736
44+
4045
-- Standard location for temporary packages needed for particular environments
4146
-- For example it is used in the project gitlab mirror to help in the MAcOS M1 build script
4247
-- See https://github.com/haskell/haskell-language-server/blob/master/.gitlab-ci.yml

ghcide/ghcide.cabal

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -68,7 +68,7 @@ library
6868
hls-plugin-api == 2.1.0.0,
6969
lens,
7070
list-t,
71-
hiedb == 0.4.3.*,
71+
hiedb ^>= 0.4.3.0,
7272
lsp-types ^>= 2.0.1.0,
7373
lsp ^>= 2.1.0.0 ,
7474
mtl,
@@ -150,6 +150,7 @@ library
150150
Development.IDE.Core.Actions
151151
Development.IDE.Main.HeapStats
152152
Development.IDE.Core.Debouncer
153+
Development.IDE.Core.Dependencies
153154
Development.IDE.Core.FileStore
154155
Development.IDE.Core.FileUtils
155156
Development.IDE.Core.IdeConfiguration

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

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ import Data.Proxy
4747
import qualified Data.Text as T
4848
import Data.Time.Clock
4949
import Data.Version
50+
import qualified Development.IDE.Core.Rules as Rules
5051
import Development.IDE.Core.RuleTypes
5152
import Development.IDE.Core.Shake hiding (Log, Priority,
5253
withHieDb)
@@ -127,6 +128,7 @@ data Log
127128
| LogNoneCradleFound FilePath
128129
| LogNewComponentCache !(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
129130
| LogHieBios HieBios.Log
131+
| LogRules Rules.Log
130132
deriving instance Show Log
131133

132134
instance Pretty Log where
@@ -197,6 +199,7 @@ instance Pretty Log where
197199
LogNewComponentCache componentCache ->
198200
"New component cache HscEnvEq:" <+> viaShow componentCache
199201
LogHieBios log -> pretty log
202+
LogRules log -> pretty log
200203

201204
-- | Bump this version number when making changes to the format of the data stored in hiedb
202205
hiedbDataVersion :: String
@@ -517,7 +520,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
517520
-- We will modify the unitId and DynFlags used for
518521
-- compilation but these are the true source of
519522
-- information.
520-
523+
521524
new_deps = RawComponentInfo (homeUnitId_ df) df targets cfp opts dep_info
522525
: maybe [] snd oldDeps
523526
-- Get all the unit-ids for things in this component
@@ -604,7 +607,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
604607

605608
-- New HscEnv for the component in question, returns the new HscEnvEq and
606609
-- a mapping from FilePath to the newly created HscEnvEq.
607-
let new_cache = newComponentCache recorder optExtensions hieYaml _cfp hscEnv uids
610+
let new_cache = newComponentCache recorder extras optExtensions hieYaml _cfp hscEnv uids
608611
(cs, res) <- new_cache new
609612
-- Modified cache targets for everything else in the hie.yaml file
610613
-- which now uses the same EPS and so on
@@ -812,14 +815,15 @@ setNameCache nc hsc = hsc { hsc_NC = nc }
812815
-- | Create a mapping from FilePaths to HscEnvEqs
813816
newComponentCache
814817
:: Recorder (WithPriority Log)
818+
-> ShakeExtras
815819
-> [String] -- File extensions to consider
816820
-> Maybe FilePath -- Path to cradle
817821
-> NormalizedFilePath -- Path to file that caused the creation of this component
818822
-> HscEnv
819823
-> [(UnitId, DynFlags)]
820824
-> ComponentInfo
821825
-> IO ( [TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
822-
newComponentCache recorder exts cradlePath cfp hsc_env uids ci = do
826+
newComponentCache recorder extras exts cradlePath cfp hsc_env uids ci = do
823827
let df = componentDynFlags ci
824828
hscEnv' <-
825829
#if MIN_VERSION_ghc(9,3,0)
@@ -842,7 +846,7 @@ newComponentCache recorder exts cradlePath cfp hsc_env uids ci = do
842846
#endif
843847

844848
let newFunc = maybe newHscEnvEqPreserveImportPaths newHscEnvEq cradlePath
845-
henv <- newFunc hscEnv' uids
849+
henv <- newFunc (cmapWithPrio LogRules recorder) extras hscEnv' uids
846850
let targetEnv = ([], Just henv)
847851
targetDepends = componentDependencyInfo ci
848852
res = (targetEnv, targetDepends)

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

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -895,34 +895,32 @@ spliceExpressions Splices{..} =
895895
-- TVar to 0 in order to set it up for a fresh indexing session. Otherwise, we
896896
-- can just increment the 'indexCompleted' TVar and exit.
897897
--
898-
indexHieFile :: ShakeExtras -> ModSummary -> NormalizedFilePath -> Util.Fingerprint -> Compat.HieFile -> IO ()
899-
indexHieFile se mod_summary srcPath !hash hf = do
898+
indexHieFile :: ShakeExtras -> NormalizedFilePath -> HieDb.SourceFile -> Util.Fingerprint -> Compat.HieFile -> IO ()
899+
indexHieFile se hiePath sourceFile !hash hf = do
900900
IdeOptions{optProgressStyle} <- getIdeOptionsIO se
901901
atomically $ do
902902
pending <- readTVar indexPending
903-
case HashMap.lookup srcPath pending of
903+
case HashMap.lookup hiePath pending of
904904
Just pendingHash | pendingHash == hash -> pure () -- An index is already scheduled
905905
_ -> do
906906
-- hiedb doesn't use the Haskell src, so we clear it to avoid unnecessarily keeping it around
907907
let !hf' = hf{hie_hs_src = mempty}
908-
modifyTVar' indexPending $ HashMap.insert srcPath hash
908+
modifyTVar' indexPending $ HashMap.insert hiePath hash
909909
writeTQueue indexQueue $ \withHieDb -> do
910910
-- We are now in the worker thread
911911
-- Check if a newer index of this file has been scheduled, and if so skip this one
912912
newerScheduled <- atomically $ do
913913
pending <- readTVar indexPending
914-
pure $ case HashMap.lookup srcPath pending of
914+
pure $ case HashMap.lookup hiePath pending of
915915
Nothing -> False
916916
-- If the hash in the pending list doesn't match the current hash, then skip
917917
Just pendingHash -> pendingHash /= hash
918918
unless newerScheduled $ do
919919
-- Using bracket, so even if an exception happen during withHieDb call,
920920
-- the `post` (which clean the progress indicator) will still be called.
921921
bracket_ (pre optProgressStyle) post $
922-
withHieDb (\db -> HieDb.addRefsFromLoaded db targetPath (HieDb.RealFile $ fromNormalizedFilePath srcPath) hash hf')
922+
withHieDb (\db -> HieDb.addRefsFromLoaded db (fromNormalizedFilePath hiePath) sourceFile hash hf')
923923
where
924-
mod_location = ms_location mod_summary
925-
targetPath = Compat.ml_hie_file mod_location
926924
HieDbWriter{..} = hiedbWriter se
927925

928926
-- Get a progress token to report progress and update it for the current file
@@ -986,15 +984,17 @@ indexHieFile se mod_summary srcPath !hash hf = do
986984
mdone <- atomically $ do
987985
-- Remove current element from pending
988986
pending <- stateTVar indexPending $
989-
dupe . HashMap.update (\pendingHash -> guard (pendingHash /= hash) $> pendingHash) srcPath
987+
dupe . HashMap.update (\pendingHash -> guard (pendingHash /= hash) $> pendingHash) hiePath
990988
modifyTVar' indexCompleted (+1)
991989
-- If we are done, report and reset completed
992990
whenMaybe (HashMap.null pending) $
993991
swapTVar indexCompleted 0
994992
whenJust (lspEnv se) $ \env -> LSP.runLspT env $
995993
when (coerce $ ideTesting se) $
996994
LSP.sendNotification (LSP.SMethod_CustomMethod (Proxy @"ghcide/reference/ready")) $
997-
toJSON $ fromNormalizedFilePath srcPath
995+
toJSON $ case sourceFile of
996+
HieDb.RealFile sourceFilePath -> sourceFilePath
997+
HieDb.FakeFile _ -> fromNormalizedFilePath hiePath
998998
whenJust mdone $ \done ->
999999
modifyVar_ indexProgressToken $ \tok -> do
10001000
whenJust (lspEnv se) $ \env -> LSP.runLspT env $
@@ -1015,7 +1015,7 @@ writeAndIndexHieFile hscEnv se mod_summary srcPath exports ast source =
10151015
GHC.mkHieFile' mod_summary exports ast source
10161016
atomicFileWrite se targetPath $ flip GHC.writeHieFile hf
10171017
hash <- Util.getFileHash targetPath
1018-
indexHieFile se mod_summary srcPath hash hf
1018+
indexHieFile se (toNormalizedFilePath' targetPath) (HieDb.RealFile $ fromNormalizedFilePath srcPath) hash hf
10191019
where
10201020
dflags = hsc_dflags hscEnv
10211021
mod_location = ms_location mod_summary
Lines changed: 162 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,162 @@
1+
module Development.IDE.Core.Dependencies
2+
( indexDependencyHieFiles
3+
) where
4+
5+
import Control.Concurrent.STM (atomically)
6+
import Control.Concurrent.STM.TQueue (writeTQueue)
7+
import Control.Monad (unless, void)
8+
import Data.Foldable (traverse_)
9+
import qualified Data.Map as Map
10+
import Data.Maybe (isNothing)
11+
import Data.Set (Set)
12+
import qualified Data.Set as Set
13+
import Development.IDE.Core.Compile (indexHieFile)
14+
import Development.IDE.Core.Rules (HieFileCheck (..), Log,
15+
checkHieFile)
16+
import Development.IDE.Core.Shake (HieDbWriter (indexQueue),
17+
ShakeExtras (hiedbWriter, lspEnv, withHieDb))
18+
import qualified Development.IDE.GHC.Compat as GHC
19+
import Development.IDE.Types.Location (NormalizedFilePath,
20+
toNormalizedFilePath')
21+
import HieDb (SourceFile (FakeFile),
22+
lookupPackage,
23+
removeDependencySrcFiles)
24+
import Ide.Logger (Recorder, WithPriority)
25+
import Language.LSP.Server (resRootPath)
26+
import System.Directory (doesDirectoryExist)
27+
import System.FilePath ((<.>), (</>))
28+
29+
newtype Package = Package GHC.UnitInfo deriving Eq
30+
instance Ord Package where
31+
compare (Package u1) (Package u2) = compare (GHC.unitId u1) (GHC.unitId u2)
32+
33+
-- indexDependencyHieFiles gets all of the direct and transitive dependencies
34+
-- from the HscEnv and indexes their HIE files in the HieDb.
35+
indexDependencyHieFiles :: Recorder (WithPriority Log) -> ShakeExtras -> GHC.HscEnv -> IO ()
36+
indexDependencyHieFiles recorder se hscEnv = do
37+
-- Check whether the .hls directory exists.
38+
dotHlsDirExists <- maybe (pure False) doesDirectoryExist mHlsDir
39+
-- If the .hls directory does not exits, it may have been deleted.
40+
-- In this case, delete the indexed source files for all
41+
-- dependencies that are already indexed.
42+
unless dotHlsDirExists deleteMissingDependencySources
43+
-- Index all dependency HIE files in the HieDb database.
44+
void $ Map.traverseWithKey indexPackageHieFiles packagesWithModules
45+
where
46+
mHlsDir :: Maybe FilePath
47+
mHlsDir = do
48+
projectDir <- resRootPath =<< lspEnv se
49+
pure $ projectDir </> ".hls"
50+
-- Add the deletion of dependency source files from the
51+
-- HieDb database to the database write queue.
52+
deleteMissingDependencySources :: IO ()
53+
deleteMissingDependencySources =
54+
atomically $ writeTQueue (indexQueue $ hiedbWriter se) $
55+
\withHieDb ->
56+
withHieDb $ \db ->
57+
removeDependencySrcFiles db
58+
-- Index all of the modules in a package (a Unit).
59+
indexPackageHieFiles :: Package -> [GHC.Module] -> IO ()
60+
indexPackageHieFiles (Package package) modules = do
61+
let pkgLibDir :: FilePath
62+
pkgLibDir = case GHC.unitLibraryDirs package of
63+
[] -> ""
64+
(libraryDir : _) -> libraryDir
65+
-- Cabal puts the HIE files for a package in the
66+
-- extra-compilation-artifacts directory, provided
67+
-- it is compiled with the -fwrite-ide-info ghc option.
68+
hieDir :: FilePath
69+
hieDir = pkgLibDir </> "extra-compilation-artifacts"
70+
unit :: GHC.Unit
71+
unit = GHC.RealUnit $ GHC.Definite $ GHC.unitId package
72+
-- Check if we have already indexed this package.
73+
moduleRows <- withHieDb se $ \db ->
74+
lookupPackage db unit
75+
case moduleRows of
76+
-- There are no modules from this package in the database,
77+
-- so go ahead and index all the modules.
78+
[] -> traverse_ (indexModuleHieFile hieDir) modules
79+
-- There are modules from this package in the database,
80+
-- so assume all the modules have already been indexed
81+
-- and do nothing.
82+
_ -> return ()
83+
indexModuleHieFile :: FilePath -> GHC.Module -> IO ()
84+
indexModuleHieFile hieDir m = do
85+
let hiePath :: NormalizedFilePath
86+
hiePath = toNormalizedFilePath' $
87+
hieDir </> GHC.moduleNameSlashes (GHC.moduleName m) <.> "hie"
88+
-- Check that the module HIE file has correctly loaded. If there
89+
-- was some problem loading it, or if it has already been indexed
90+
-- (which shouldn't happen because we check whether each package
91+
-- has been indexed), then do nothing. Otherwise, call the
92+
-- indexHieFile function from Core.Compile.
93+
hieCheck <- checkHieFile recorder se "newHscEnvEqWithImportPaths" hiePath
94+
case hieCheck of
95+
HieFileMissing -> return ()
96+
HieAlreadyIndexed -> return ()
97+
CouldNotLoadHie _e -> return ()
98+
DoIndexing hash hie ->
99+
-- At this point there is no source file for the HIE file,
100+
-- so the HieDb.SourceFile we give is FakeFile Nothing.
101+
indexHieFile se hiePath (FakeFile Nothing) hash hie
102+
packagesWithModules :: Map.Map Package [GHC.Module]
103+
packagesWithModules = Map.fromSet getModulesForPackage packages
104+
packages :: Set Package
105+
packages = Set.fromList
106+
$ map Package
107+
$ Map.elems
108+
-- Take only the packages in the unitInfoMap that are direct
109+
-- or transitive dependencies.
110+
$ Map.filterWithKey (\uid _ -> uid `Set.member` dependencyIds) unitInfoMap
111+
where
112+
unitInfoMap :: GHC.UnitInfoMap
113+
unitInfoMap = GHC.getUnitInfoMap hscEnv
114+
dependencyIds :: Set GHC.UnitId
115+
dependencyIds =
116+
calculateTransitiveDependencies unitInfoMap directDependencyIds directDependencyIds
117+
directDependencyIds :: Set GHC.UnitId
118+
directDependencyIds = Set.fromList
119+
$ map GHC.toUnitId
120+
$ GHC.explicitUnits
121+
$ GHC.unitState hscEnv
122+
123+
-- calculateTransitiveDependencies finds the UnitId keys in the UnitInfoMap
124+
-- that are dependencies or transitive dependencies.
125+
calculateTransitiveDependencies :: GHC.UnitInfoMap -> Set GHC.UnitId -> Set GHC.UnitId -> Set GHC.UnitId
126+
calculateTransitiveDependencies unitInfoMap allDependencies newDepencencies
127+
-- If there are no new dependencies, we have found them all,
128+
-- so return allDependencies
129+
| Set.null newDepencencies = allDependencies
130+
-- Otherwise recursively add any dependencies of the newDepencencies
131+
-- that are not in allDependencies already.
132+
| otherwise = calculateTransitiveDependencies unitInfoMap nextAll nextNew
133+
where
134+
nextAll :: Set GHC.UnitId
135+
nextAll = Set.union allDependencies nextNew
136+
-- Get the dependencies of the newDependencies. Then the nextNew depencencies
137+
-- will be the set difference of the dependencies we have so far (allDependencies),
138+
-- and the dependencies of the newDepencencies.
139+
nextNew :: Set GHC.UnitId
140+
nextNew = flip Set.difference allDependencies
141+
$ Set.unions
142+
$ map (Set.fromList . GHC.unitDepends)
143+
$ Map.elems
144+
$ Map.filterWithKey (\uid _ -> uid `Set.member` newDepencencies) unitInfoMap
145+
146+
getModulesForPackage :: Package -> [GHC.Module]
147+
getModulesForPackage (Package package) =
148+
map makeModule allModules
149+
where
150+
allModules :: [GHC.ModuleName]
151+
allModules = map fst
152+
-- The modules with a Just value in the tuple
153+
-- are from other packages. These won't have
154+
-- an HIE file in this package, and should be
155+
-- covered by the transitive dependencies.
156+
( filter (isNothing . snd)
157+
$ GHC.unitExposedModules package
158+
)
159+
++ GHC.unitHiddenModules package
160+
makeModule :: GHC.ModuleName
161+
-> GHC.Module
162+
makeModule = GHC.mkModule (GHC.unitInfoId package)

0 commit comments

Comments
 (0)