Skip to content

Commit e87f1d1

Browse files
committed
add fingerprints rules for module graph:
GetModuleGraphTransDepsFingerprints,GetModuleGraphTransReverseDepsFingerprints,GetModuleGraphImmediateReverseDepsFingerprints.
1 parent 4ec8a6f commit e87f1d1

File tree

5 files changed

+71
-29
lines changed

5 files changed

+71
-29
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -264,7 +264,7 @@ typecheckParents recorder state nfp = void $ shakeEnqueue (shakeExtras state) pa
264264

265265
typecheckParentsAction :: Recorder (WithPriority Log) -> NormalizedFilePath -> Action ()
266266
typecheckParentsAction recorder nfp = do
267-
revs <- transitiveReverseDependencies nfp <$> useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph nfp
267+
revs <- transitiveReverseDependencies nfp <$> useWithSeparateFingerprintRule_ GetModuleGraphTransReverseDepsFingerprints GetModuleGraph nfp
268268
case revs of
269269
Nothing -> logWith recorder Info $ LogCouldNotIdentifyReverseDeps nfp
270270
Just rs -> do

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

Lines changed: 16 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,9 @@ type instance RuleResult GetModuleGraph = DependencyInformation
7676

7777
-- | it only compute the fingerprint of the module graph for a file and its dependencies
7878
-- we need this to trigger recompilation when the sub module graph for a file changes
79-
type instance RuleResult GetFileModuleGraphFingerprint = Fingerprint
79+
type instance RuleResult GetModuleGraphTransDepsFingerprints = Fingerprint
80+
type instance RuleResult GetModuleGraphTransReverseDepsFingerprints = Fingerprint
81+
type instance RuleResult GetModuleGraphImmediateReverseDepsFingerprints = Fingerprint
8082

8183
data GetKnownTargets = GetKnownTargets
8284
deriving (Show, Generic, Eq, Ord)
@@ -421,10 +423,20 @@ data GetModuleGraph = GetModuleGraph
421423
instance Hashable GetModuleGraph
422424
instance NFData GetModuleGraph
423425

424-
data GetFileModuleGraphFingerprint = GetFileModuleGraphFingerprint
426+
data GetModuleGraphTransDepsFingerprints = GetModuleGraphTransDepsFingerprints
425427
deriving (Eq, Show, Generic)
426-
instance Hashable GetFileModuleGraphFingerprint
427-
instance NFData GetFileModuleGraphFingerprint
428+
instance Hashable GetModuleGraphTransDepsFingerprints
429+
instance NFData GetModuleGraphTransDepsFingerprints
430+
431+
data GetModuleGraphTransReverseDepsFingerprints = GetModuleGraphTransReverseDepsFingerprints
432+
deriving (Eq, Show, Generic)
433+
instance Hashable GetModuleGraphTransReverseDepsFingerprints
434+
instance NFData GetModuleGraphTransReverseDepsFingerprints
435+
436+
data GetModuleGraphImmediateReverseDepsFingerprints = GetModuleGraphImmediateReverseDepsFingerprints
437+
deriving (Eq, Show, Generic)
438+
instance Hashable GetModuleGraphImmediateReverseDepsFingerprints
439+
instance NFData GetModuleGraphImmediateReverseDepsFingerprints
428440

429441
data ReportImportCycles = ReportImportCycles
430442
deriving (Eq, Show, Generic)

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

Lines changed: 15 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -472,7 +472,7 @@ rawDependencyInformation fs = do
472472
reportImportCyclesRule :: Recorder (WithPriority Log) -> Rules ()
473473
reportImportCyclesRule recorder =
474474
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \ReportImportCycles file -> fmap (\errs -> if null errs then (Just "1",([], Just ())) else (Nothing, (errs, Nothing))) $ do
475-
DependencyInformation{..} <- useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph file
475+
DependencyInformation{..} <- useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph file
476476
case pathToId depPathIdMap file of
477477
-- The header of the file does not parse, so it can't be part of any import cycles.
478478
Nothing -> pure []
@@ -628,12 +628,6 @@ getModuleGraphRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake rec
628628
fs <- toKnownFiles <$> useNoFile_ GetKnownTargets
629629
dependencyInfoForFiles (HashSet.toList fs)
630630

631-
getModuleGraphSingleFileRule :: Recorder (WithPriority Log) -> Rules ()
632-
getModuleGraphSingleFileRule recorder =
633-
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \GetFileModuleGraphFingerprint file -> do
634-
di <- useNoFile_ GetModuleGraph
635-
return $ lookupFingerprint file di
636-
637631
dependencyInfoForFiles :: [NormalizedFilePath] -> Action (BS.ByteString, DependencyInformation)
638632
dependencyInfoForFiles fs = do
639633
(rawDepInfo, bm) <- rawDependencyInformation fs
@@ -669,7 +663,7 @@ typeCheckRuleDefinition hsc pm fp = do
669663
unlift <- askUnliftIO
670664
let dets = TypecheckHelpers
671665
{ getLinkables = unliftIO unlift . uses_ GetLinkable
672-
, getModuleGraph = unliftIO unlift $ useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph fp
666+
, getModuleGraph = unliftIO unlift $ useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph fp
673667
}
674668
addUsageDependencies $ liftIO $
675669
typecheckModule defer hsc dets pm
@@ -768,7 +762,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
768762
let inLoadOrder = map (\HiFileResult{..} -> HomeModInfo hirModIface hirModDetails emptyHomeModInfoLinkable) ifaces
769763
mg <- do
770764
if fullModuleGraph
771-
then depModuleGraph <$> useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph file
765+
then depModuleGraph <$> useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph file
772766
else do
773767
let mgs = map hsc_mod_graph depSessions
774768
-- On GHC 9.4+, the module graph contains not only ModSummary's but each `ModuleNode` in the graph
@@ -781,7 +775,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
781775
nubOrdOn mkNodeKey (ModuleNode final_deps ms : concatMap mgModSummaries' mgs)
782776
liftIO $ evaluate $ liftRnf rwhnf module_graph_nodes
783777
return $ mkModuleGraph module_graph_nodes
784-
de <- useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph file
778+
de <- useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph file
785779
session' <- liftIO $ mergeEnvs hsc mg de ms inLoadOrder depSessions
786780

787781
-- Here we avoid a call to to `newHscEnvEqWithImportPaths`, which creates a new
@@ -811,7 +805,7 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco
811805
, old_value = m_old
812806
, get_file_version = use GetModificationTime_{missingFileDiagnostics = False}
813807
, get_linkable_hashes = \fs -> map (snd . fromJust . hirCoreFp) <$> uses_ GetModIface fs
814-
, get_module_graph = useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph f
808+
, get_module_graph = useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph f
815809
, regenerate = regenerateHiFile session f ms
816810
}
817811
hsc_env' <- setFileCacheHook (hscEnv session)
@@ -1145,7 +1139,7 @@ needsCompilationRule file
11451139
| "boot" `isSuffixOf` fromNormalizedFilePath file =
11461140
pure (Just $ encodeLinkableType Nothing, Just Nothing)
11471141
needsCompilationRule file = do
1148-
graph <- useWithSeparateFingerprintRule GetFileModuleGraphFingerprint GetModuleGraph file
1142+
graph <- useWithSeparateFingerprintRule GetModuleGraphImmediateReverseDepsFingerprints GetModuleGraph file
11491143
res <- case graph of
11501144
-- Treat as False if some reverse dependency header fails to parse
11511145
Nothing -> pure Nothing
@@ -1236,7 +1230,6 @@ mainRule recorder RulesConfig{..} = do
12361230
getModIfaceRule recorder
12371231
getModSummaryRule templateHaskellWarning recorder
12381232
getModuleGraphRule recorder
1239-
getModuleGraphSingleFileRule recorder
12401233
getFileHashRule recorder
12411234
knownFilesRule recorder
12421235
getClientSettingsRule recorder
@@ -1258,6 +1251,15 @@ mainRule recorder RulesConfig{..} = do
12581251
persistentDocMapRule
12591252
persistentImportMapRule
12601253
getLinkableRule recorder
1254+
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \GetModuleGraphTransDepsFingerprints file -> do
1255+
di <- useNoFile_ GetModuleGraph
1256+
return $ lookupFingerprint file di (depTransDepsFingerprints di)
1257+
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \GetModuleGraphTransReverseDepsFingerprints file -> do
1258+
di <- useNoFile_ GetModuleGraph
1259+
return $ lookupFingerprint file di (depTransReverseDepsFingerprints di)
1260+
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \GetModuleGraphImmediateReverseDepsFingerprints file -> do
1261+
di <- useNoFile_ GetModuleGraph
1262+
return $ lookupFingerprint file di (depImmediateReverseDepsFingerprints di)
12611263

12621264
-- | Get HieFile for haskell file on NormalizedFilePath
12631265
getHieFile :: NormalizedFilePath -> Action (Maybe HieFile)

ghcide/src/Development/IDE/Import/DependencyInformation.hs

Lines changed: 36 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -154,15 +154,19 @@ data DependencyInformation =
154154
, depModuleFiles :: !(ShowableModuleEnv FilePathId)
155155
-- ^ Map from Module to the corresponding non-boot hs file
156156
, depModuleGraph :: !ModuleGraph
157-
-- ^ Map from Module to the
158-
, depModuleFingerprints :: !(FilePathIdMap Fingerprint)
157+
-- ^ Map from Module to fingerprint of the transitive dependencies of the module.
158+
, depTransDepsFingerprints :: !(FilePathIdMap Fingerprint)
159+
-- ^ Map from FilePathId to the fingerprint of the transitive reverse dependencies of the module.
160+
, depTransReverseDepsFingerprints :: !(FilePathIdMap Fingerprint)
161+
-- ^ Map from FilePathId to the fingerprint of the immediate reverse dependencies of the module.
162+
, depImmediateReverseDepsFingerprints :: !(FilePathIdMap Fingerprint)
159163
} deriving (Show, Generic)
160164

161-
lookupFingerprint :: NormalizedFilePath -> DependencyInformation -> Maybe Fingerprint
162-
lookupFingerprint fileId DependencyInformation {..} =
165+
lookupFingerprint :: NormalizedFilePath -> DependencyInformation -> FilePathIdMap Fingerprint -> Maybe Fingerprint
166+
lookupFingerprint fileId DependencyInformation {..} depFingerprintMap =
163167
do
164168
FilePathId cur_id <- lookupPathToId depPathIdMap fileId
165-
IntMap.lookup cur_id depModuleFingerprints
169+
IntMap.lookup cur_id depFingerprintMap
166170

167171
newtype ShowableModule =
168172
ShowableModule {showableModule :: Module}
@@ -250,7 +254,9 @@ processDependencyInformation RawDependencyInformation{..} rawBootMap mg shallowF
250254
, depBootMap = rawBootMap
251255
, depModuleFiles = ShowableModuleEnv reverseModuleMap
252256
, depModuleGraph = mg
253-
, depModuleFingerprints = buildAccFingerFilePathIdMap moduleDeps shallowFingerMap
257+
, depTransDepsFingerprints = buildTransDepsFingerprintMap moduleDeps shallowFingerMap
258+
, depTransReverseDepsFingerprints = buildTransDepsFingerprintMap reverseModuleDeps shallowFingerMap
259+
, depImmediateReverseDepsFingerprints = buildImmediateDepsFingerprintMap reverseModuleDeps shallowFingerMap
254260
}
255261
where resultGraph = buildResultGraph rawImports
256262
(errorNodes, successNodes) = partitionNodeResults $ IntMap.toList resultGraph
@@ -411,11 +417,33 @@ instance NFData NamedModuleDep where
411417
instance Show NamedModuleDep where
412418
show NamedModuleDep{..} = show nmdFilePath
413419

420+
421+
buildImmediateDepsFingerprintMap :: FilePathIdMap FilePathIdSet -> FilePathIdMap Fingerprint -> FilePathIdMap Fingerprint
422+
buildImmediateDepsFingerprintMap modulesDeps shallowFingers = go keys IntMap.empty
423+
where
424+
keys = IntMap.keys shallowFingers
425+
go :: [IntSet.Key] -> FilePathIdMap Fingerprint -> FilePathIdMap Fingerprint
426+
go keys acc =
427+
case keys of
428+
[] -> acc
429+
k : ks ->
430+
if IntMap.member k acc
431+
-- already in the map, so we can skip
432+
then go ks acc
433+
-- not in the map, so we need to add it
434+
else
435+
let -- get the dependencies of the current key
436+
deps = IntSet.toList $ IntMap.findWithDefault IntSet.empty k modulesDeps
437+
-- combine the fingerprints of the dependencies with the current key
438+
combinedFingerprints = Util.fingerprintFingerprints $ map (shallowFingers IntMap.!) (k:deps)
439+
in -- add the combined fingerprints to the accumulator
440+
go ks (IntMap.insert k combinedFingerprints acc)
441+
414442
-- | Build a map from file path to its full fingerprint.
415443
-- The fingerprint is depend on both the fingerprints of the file and all its dependencies.
416444
-- This is used to determine if a file has changed and needs to be reloaded.
417-
buildAccFingerFilePathIdMap :: FilePathIdMap FilePathIdSet -> FilePathIdMap Fingerprint -> FilePathIdMap Fingerprint
418-
buildAccFingerFilePathIdMap modulesDeps shallowFingers = go keys IntMap.empty
445+
buildTransDepsFingerprintMap :: FilePathIdMap FilePathIdSet -> FilePathIdMap Fingerprint -> FilePathIdMap Fingerprint
446+
buildTransDepsFingerprintMap modulesDeps shallowFingers = go keys IntMap.empty
419447
where
420448
keys = IntMap.keys shallowFingers
421449
go :: [IntSet.Key] -> FilePathIdMap Fingerprint -> FilePathIdMap Fingerprint

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Handlers.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -72,12 +72,12 @@ import GHC (ClsInst,
7272

7373
import Development.IDE.Core.RuleTypes (GetLinkable (GetLinkable),
7474
GetModSummary (GetModSummary),
75-
GetFileModuleGraphFingerprint (GetFileModuleGraphFingerprint),
75+
GetModuleGraphTransDepsFingerprints (GetModuleGraphTransDepsFingerprints),
7676
GhcSessionDeps (GhcSessionDeps),
7777
ModSummaryResult (msrModSummary),
7878
LinkableResult (linkableHomeMod),
7979
TypeCheck (..),
80-
tmrTypechecked, GetFileModuleGraphFingerprint(..), GetModuleGraph(..))
80+
tmrTypechecked, GetModuleGraphTransDepsFingerprints(..), GetModuleGraph(..))
8181
import qualified Development.IDE.GHC.Compat.Core as Compat (InteractiveImport (IIModule))
8282
import qualified Development.IDE.GHC.Compat.Core as SrcLoc (unLoc)
8383
import Development.IDE.Types.HscEnvEq (HscEnvEq (hscEnv))
@@ -253,7 +253,7 @@ initialiseSessionForEval needs_quickcheck st nfp = do
253253
ms <- msrModSummary <$> use_ GetModSummary nfp
254254
deps_hsc <- hscEnv <$> use_ GhcSessionDeps nfp
255255

256-
linkables_needed <- transitiveDeps <$> useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph nfp <*> pure nfp
256+
linkables_needed <- transitiveDeps <$> useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph nfp <*> pure nfp
257257
linkables <- uses_ GetLinkable (nfp : maybe [] transitiveModuleDeps linkables_needed)
258258
-- We unset the global rdr env in mi_globals when we generate interfaces
259259
-- See Note [Clearing mi_globals after generating an iface]

0 commit comments

Comments
 (0)