Skip to content

Commit 824c508

Browse files
committed
compute deps fingerprint only
1 parent e00b5dd commit 824c508

File tree

5 files changed

+79
-22
lines changed

5 files changed

+79
-22
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 <$> useNoFile_ GetModuleGraph
267+
revs <- transitiveReverseDependencies nfp <$> use_ GetFileModuleGraph 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: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -74,6 +74,9 @@ type instance RuleResult GetParsedModuleWithComments = ParsedModule
7474

7575
type instance RuleResult GetModuleGraph = DependencyInformation
7676

77+
-- same as DependencyInformation but only rebuilds if the target file deps changes
78+
type instance RuleResult GetFileModuleGraph = DependencyInformation
79+
7780
data GetKnownTargets = GetKnownTargets
7881
deriving (Show, Generic, Eq, Ord)
7982
instance Hashable GetKnownTargets
@@ -417,6 +420,11 @@ data GetModuleGraph = GetModuleGraph
417420
instance Hashable GetModuleGraph
418421
instance NFData GetModuleGraph
419422

423+
data GetFileModuleGraph = GetFileModuleGraph
424+
deriving (Eq, Show, Generic)
425+
instance Hashable GetFileModuleGraph
426+
instance NFData GetFileModuleGraph
427+
420428
data ReportImportCycles = ReportImportCycles
421429
deriving (Eq, Show, Generic)
422430
instance Hashable ReportImportCycles

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

Lines changed: 20 additions & 9 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{..} <- useNoFile_ GetModuleGraph
475+
DependencyInformation{..} <- use_ GetFileModuleGraph 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 []
@@ -608,7 +608,7 @@ typeCheckRule recorder = define (cmapWithPrio LogShake recorder) $ \TypeCheck fi
608608
-- very expensive.
609609
when (foi == NotFOI) $
610610
logWith recorder Logger.Warning $ LogTypecheckedFOI file
611-
typeCheckRuleDefinition hsc pm
611+
typeCheckRuleDefinition hsc pm file
612612

613613
knownFilesRule :: Recorder (WithPriority Log) -> Rules ()
614614
knownFilesRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake recorder) $ \GetKnownTargets -> do
@@ -628,6 +628,12 @@ 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+
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetFileModuleGraph file -> do
634+
di <- useNoFile_ GetModuleGraph
635+
return (fingerprintToBS <$> lookupFingerprint file di, ([], Just di))
636+
631637
dependencyInfoForFiles :: [NormalizedFilePath] -> Action (BS.ByteString, DependencyInformation)
632638
dependencyInfoForFiles fs = do
633639
(rawDepInfo, bm) <- rawDependencyInformation fs
@@ -643,7 +649,10 @@ dependencyInfoForFiles fs = do
643649
go (Just ms) _ = Just $ ModuleNode [] ms
644650
go _ _ = Nothing
645651
mg = mkModuleGraph mns
646-
pure (fingerprintToBS $ Util.fingerprintFingerprints $ map (maybe fingerprint0 msrFingerprint) msrs, processDependencyInformation rawDepInfo bm mg)
652+
let shallowFingers = IntMap.fromList $ foldr' (\(i, m) acc -> case m of
653+
Just x -> (getFilePathId i,msrFingerprint x):acc
654+
Nothing -> acc) [] $ zip _all_ids msrs
655+
pure (fingerprintToBS $ Util.fingerprintFingerprints $ map (maybe fingerprint0 msrFingerprint) msrs, processDependencyInformation rawDepInfo bm mg shallowFingers)
647656

648657
-- This is factored out so it can be directly called from the GetModIface
649658
-- rule. Directly calling this rule means that on the initial load we can
@@ -652,14 +661,15 @@ dependencyInfoForFiles fs = do
652661
typeCheckRuleDefinition
653662
:: HscEnv
654663
-> ParsedModule
664+
-> NormalizedFilePath
655665
-> Action (IdeResult TcModuleResult)
656-
typeCheckRuleDefinition hsc pm = do
666+
typeCheckRuleDefinition hsc pm fp = do
657667
IdeOptions { optDefer = defer } <- getIdeOptions
658668

659669
unlift <- askUnliftIO
660670
let dets = TypecheckHelpers
661671
{ getLinkables = unliftIO unlift . uses_ GetLinkable
662-
, getModuleGraph = unliftIO unlift $ useNoFile_ GetModuleGraph
672+
, getModuleGraph = unliftIO unlift $ use_ GetFileModuleGraph fp
663673
}
664674
addUsageDependencies $ liftIO $
665675
typecheckModule defer hsc dets pm
@@ -758,7 +768,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
758768
let inLoadOrder = map (\HiFileResult{..} -> HomeModInfo hirModIface hirModDetails emptyHomeModInfoLinkable) ifaces
759769
mg <- do
760770
if fullModuleGraph
761-
then depModuleGraph <$> useNoFile_ GetModuleGraph
771+
then depModuleGraph <$> use_ GetFileModuleGraph file
762772
else do
763773
let mgs = map hsc_mod_graph depSessions
764774
-- On GHC 9.4+, the module graph contains not only ModSummary's but each `ModuleNode` in the graph
@@ -771,7 +781,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
771781
nubOrdOn mkNodeKey (ModuleNode final_deps ms : concatMap mgModSummaries' mgs)
772782
liftIO $ evaluate $ liftRnf rwhnf module_graph_nodes
773783
return $ mkModuleGraph module_graph_nodes
774-
de <- useNoFile_ GetModuleGraph
784+
de <- use_ GetFileModuleGraph file
775785
session' <- liftIO $ mergeEnvs hsc mg de ms inLoadOrder depSessions
776786

777787
-- Here we avoid a call to to `newHscEnvEqWithImportPaths`, which creates a new
@@ -801,7 +811,7 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco
801811
, old_value = m_old
802812
, get_file_version = use GetModificationTime_{missingFileDiagnostics = False}
803813
, get_linkable_hashes = \fs -> map (snd . fromJust . hirCoreFp) <$> uses_ GetModIface fs
804-
, get_module_graph = useNoFile_ GetModuleGraph
814+
, get_module_graph = use_ GetFileModuleGraph f
805815
, regenerate = regenerateHiFile session f ms
806816
}
807817
hsc_env' <- setFileCacheHook (hscEnv session)
@@ -977,7 +987,7 @@ regenerateHiFile sess f ms compNeeded = do
977987
Just pm -> do
978988
-- Invoke typechecking directly to update it without incurring a dependency
979989
-- on the parsed module and the typecheck rules
980-
(diags', mtmr) <- typeCheckRuleDefinition hsc pm
990+
(diags', mtmr) <- typeCheckRuleDefinition hsc pm f
981991
case mtmr of
982992
Nothing -> pure (diags', Nothing)
983993
Just tmr -> do
@@ -1226,6 +1236,7 @@ mainRule recorder RulesConfig{..} = do
12261236
getModIfaceRule recorder
12271237
getModSummaryRule templateHaskellWarning recorder
12281238
getModuleGraphRule recorder
1239+
getModuleGraphSingleFileRule recorder
12291240
getFileHashRule recorder
12301241
knownFilesRule recorder
12311242
getClientSettingsRule recorder

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

Lines changed: 48 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ module Development.IDE.Import.DependencyInformation
2929
, lookupModuleFile
3030
, BootIdMap
3131
, insertBootId
32+
, lookupFingerprint
3233
) where
3334

3435
import Control.DeepSeq
@@ -49,6 +50,8 @@ import qualified Data.List.NonEmpty as NonEmpty
4950
import Data.Maybe
5051
import Data.Tuple.Extra hiding (first, second)
5152
import Development.IDE.GHC.Compat
53+
import Development.IDE.GHC.Compat.Util (Fingerprint)
54+
import qualified Development.IDE.GHC.Compat.Util as Util
5255
import Development.IDE.GHC.Orphans ()
5356
import Development.IDE.Import.FindImports (ArtifactsLocation (..))
5457
import Development.IDE.Types.Diagnostics
@@ -136,23 +139,31 @@ data RawDependencyInformation = RawDependencyInformation
136139

137140
data DependencyInformation =
138141
DependencyInformation
139-
{ depErrorNodes :: !(FilePathIdMap (NonEmpty NodeError))
142+
{ depErrorNodes :: !(FilePathIdMap (NonEmpty NodeError))
140143
-- ^ Nodes that cannot be processed correctly.
141-
, depModules :: !(FilePathIdMap ShowableModule)
142-
, depModuleDeps :: !(FilePathIdMap FilePathIdSet)
144+
, depModules :: !(FilePathIdMap ShowableModule)
145+
, depModuleDeps :: !(FilePathIdMap FilePathIdSet)
143146
-- ^ For a non-error node, this contains the set of module immediate dependencies
144147
-- in the same package.
145-
, depReverseModuleDeps :: !(IntMap IntSet)
148+
, depReverseModuleDeps :: !(IntMap IntSet)
146149
-- ^ Contains a reverse mapping from a module to all those that immediately depend on it.
147-
, depPathIdMap :: !PathIdMap
150+
, depPathIdMap :: !PathIdMap
148151
-- ^ Map from FilePath to FilePathId
149-
, depBootMap :: !BootIdMap
152+
, depBootMap :: !BootIdMap
150153
-- ^ Map from hs-boot file to the corresponding hs file
151-
, depModuleFiles :: !(ShowableModuleEnv FilePathId)
154+
, depModuleFiles :: !(ShowableModuleEnv FilePathId)
152155
-- ^ Map from Module to the corresponding non-boot hs file
153-
, depModuleGraph :: !ModuleGraph
156+
, depModuleGraph :: !ModuleGraph
157+
-- ^ Map from Module to the
158+
, depModuleFingerprints :: !(FilePathIdMap Fingerprint)
154159
} deriving (Show, Generic)
155160

161+
lookupFingerprint :: NormalizedFilePath -> DependencyInformation -> Maybe Fingerprint
162+
lookupFingerprint fileId DependencyInformation {..} =
163+
do
164+
FilePathId cur_id <- lookupPathToId depPathIdMap fileId
165+
IntMap.lookup cur_id depModuleFingerprints
166+
156167
newtype ShowableModule =
157168
ShowableModule {showableModule :: Module}
158169
deriving NFData
@@ -228,8 +239,8 @@ instance Semigroup NodeResult where
228239
SuccessNode _ <> ErrorNode errs = ErrorNode errs
229240
SuccessNode a <> SuccessNode _ = SuccessNode a
230241

231-
processDependencyInformation :: RawDependencyInformation -> BootIdMap -> ModuleGraph -> DependencyInformation
232-
processDependencyInformation RawDependencyInformation{..} rawBootMap mg =
242+
processDependencyInformation :: RawDependencyInformation -> BootIdMap -> ModuleGraph -> FilePathIdMap Fingerprint -> DependencyInformation
243+
processDependencyInformation RawDependencyInformation{..} rawBootMap mg shallowFingerMap =
233244
DependencyInformation
234245
{ depErrorNodes = IntMap.fromList errorNodes
235246
, depModuleDeps = moduleDeps
@@ -239,6 +250,7 @@ processDependencyInformation RawDependencyInformation{..} rawBootMap mg =
239250
, depBootMap = rawBootMap
240251
, depModuleFiles = ShowableModuleEnv reverseModuleMap
241252
, depModuleGraph = mg
253+
, depModuleFingerprints = buildAccFingerFilePathIdMap moduleDeps shallowFingerMap
242254
}
243255
where resultGraph = buildResultGraph rawImports
244256
(errorNodes, successNodes) = partitionNodeResults $ IntMap.toList resultGraph
@@ -398,3 +410,29 @@ instance NFData NamedModuleDep where
398410

399411
instance Show NamedModuleDep where
400412
show NamedModuleDep{..} = show nmdFilePath
413+
414+
-- | Build a map from file path to fingerprint. The fingerprint is built
415+
-- from the fingerprints of the file and all its dependencies.
416+
-- 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
419+
where
420+
keys = IntMap.keys shallowFingers
421+
go :: [IntSet.Key] -> FilePathIdMap Fingerprint -> FilePathIdMap Fingerprint
422+
go keys acc =
423+
case keys of
424+
[] -> acc
425+
k : ks ->
426+
if IntMap.member k acc
427+
-- already in the map, so we can skip
428+
then go ks acc
429+
-- not in the map, so we need to add it
430+
else
431+
let -- get the dependencies of the current key
432+
deps = IntSet.toList $ IntMap.findWithDefault IntSet.empty k modulesDeps
433+
-- add fingerprints of the dependencies to the accumulator
434+
depFingerprints = go deps acc
435+
-- combine the fingerprints of the dependencies with the current key
436+
combinedFingerprints = Util.fingerprintFingerprints $ shallowFingers IntMap.! k : map (depFingerprints IntMap.!) deps
437+
in -- add the combined fingerprints to the accumulator
438+
go ks (IntMap.insert k combinedFingerprints depFingerprints)

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ import Development.IDE.Core.Rules (IdeState,
4646
runAction)
4747
import Development.IDE.Core.RuleTypes (LinkableResult (linkableHomeMod),
4848
TypeCheck (..),
49-
tmrTypechecked)
49+
tmrTypechecked, GetFileModuleGraph(..))
5050
import Development.IDE.Core.Shake (useNoFile_, use_,
5151
uses_)
5252
import Development.IDE.GHC.Compat hiding (typeKind,
@@ -256,7 +256,7 @@ initialiseSessionForEval needs_quickcheck st nfp = do
256256
ms <- msrModSummary <$> use_ GetModSummary nfp
257257
deps_hsc <- hscEnv <$> use_ GhcSessionDeps nfp
258258

259-
linkables_needed <- transitiveDeps <$> useNoFile_ GetModuleGraph <*> pure nfp
259+
linkables_needed <- transitiveDeps <$> use_ GetFileModuleGraph nfp <*> pure nfp
260260
linkables <- uses_ GetLinkable (nfp : maybe [] transitiveModuleDeps linkables_needed)
261261
-- We unset the global rdr env in mi_globals when we generate interfaces
262262
-- See Note [Clearing mi_globals after generating an iface]

0 commit comments

Comments
 (0)