Skip to content

Commit 101f0f6

Browse files
committed
Revert "Improve caching granularity by using partial fingerprints of ModuleGraph haskell#4594"
This reverts commit 997a426.
1 parent ceff4d0 commit 101f0f6

File tree

6 files changed

+32
-145
lines changed

6 files changed

+32
-145
lines changed

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

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

290290
typecheckParentsAction :: Recorder (WithPriority Log) -> NormalizedFilePath -> Action ()
291291
typecheckParentsAction recorder nfp = do
292-
revs <- transitiveReverseDependencies nfp <$> useWithSeparateFingerprintRule_ GetModuleGraphTransReverseDepsFingerprints GetModuleGraph nfp
292+
revs <- transitiveReverseDependencies nfp <$> useNoFile_ GetModuleGraph
293293
case revs of
294294
Nothing -> logWith recorder Info $ LogCouldNotIdentifyReverseDeps nfp
295295
Just rs -> do

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

Lines changed: 0 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -78,12 +78,6 @@ type instance RuleResult GetParsedModuleWithComments = ParsedModule
7878

7979
type instance RuleResult GetModuleGraph = DependencyInformation
8080

81-
-- | it only compute the fingerprint of the module graph for a file and its dependencies
82-
-- we need this to trigger recompilation when the sub module graph for a file changes
83-
type instance RuleResult GetModuleGraphTransDepsFingerprints = Fingerprint
84-
type instance RuleResult GetModuleGraphTransReverseDepsFingerprints = Fingerprint
85-
type instance RuleResult GetModuleGraphImmediateReverseDepsFingerprints = Fingerprint
86-
8781
data GetKnownTargets = GetKnownTargets
8882
deriving (Show, Generic, Eq, Ord)
8983
instance Hashable GetKnownTargets
@@ -440,21 +434,6 @@ data GetModuleGraph = GetModuleGraph
440434
instance Hashable GetModuleGraph
441435
instance NFData GetModuleGraph
442436

443-
data GetModuleGraphTransDepsFingerprints = GetModuleGraphTransDepsFingerprints
444-
deriving (Eq, Show, Generic)
445-
instance Hashable GetModuleGraphTransDepsFingerprints
446-
instance NFData GetModuleGraphTransDepsFingerprints
447-
448-
data GetModuleGraphTransReverseDepsFingerprints = GetModuleGraphTransReverseDepsFingerprints
449-
deriving (Eq, Show, Generic)
450-
instance Hashable GetModuleGraphTransReverseDepsFingerprints
451-
instance NFData GetModuleGraphTransReverseDepsFingerprints
452-
453-
data GetModuleGraphImmediateReverseDepsFingerprints = GetModuleGraphImmediateReverseDepsFingerprints
454-
deriving (Eq, Show, Generic)
455-
instance Hashable GetModuleGraphImmediateReverseDepsFingerprints
456-
instance NFData GetModuleGraphImmediateReverseDepsFingerprints
457-
458437
data ReportImportCycles = ReportImportCycles
459438
deriving (Eq, Show, Generic)
460439
instance Hashable ReportImportCycles

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

Lines changed: 10 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -477,7 +477,7 @@ rawDependencyInformation fs = do
477477
reportImportCyclesRule :: Recorder (WithPriority Log) -> Rules ()
478478
reportImportCyclesRule recorder =
479479
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \ReportImportCycles file -> fmap (\errs -> if null errs then (Just "1",([], Just ())) else (Nothing, (errs, Nothing))) $ do
480-
DependencyInformation{..} <- useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph file
480+
DependencyInformation{..} <- useNoFile_ GetModuleGraph
481481
case pathToId depPathIdMap file of
482482
-- The header of the file does not parse, so it can't be part of any import cycles.
483483
Nothing -> pure []
@@ -613,7 +613,7 @@ typeCheckRule recorder = define (cmapWithPrio LogShake recorder) $ \TypeCheck fi
613613
-- very expensive.
614614
when (foi == NotFOI) $
615615
logWith recorder Logger.Warning $ LogTypecheckedFOI file
616-
typeCheckRuleDefinition hsc pm file
616+
typeCheckRuleDefinition hsc pm
617617

618618
knownFilesRule :: Recorder (WithPriority Log) -> Rules ()
619619
knownFilesRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake recorder) $ \GetKnownTargets -> do
@@ -648,10 +648,7 @@ dependencyInfoForFiles fs = do
648648
go (Just ms) _ = Just $ ModuleNode [] ms
649649
go _ _ = Nothing
650650
mg = mkModuleGraph mns
651-
let shallowFingers = IntMap.fromList $ foldr' (\(i, m) acc -> case m of
652-
Just x -> (getFilePathId i,msrFingerprint x):acc
653-
Nothing -> acc) [] $ zip _all_ids msrs
654-
pure (fingerprintToBS $ Util.fingerprintFingerprints $ map (maybe fingerprint0 msrFingerprint) msrs, processDependencyInformation rawDepInfo bm mg shallowFingers)
651+
pure (fingerprintToBS $ Util.fingerprintFingerprints $ map (maybe fingerprint0 msrFingerprint) msrs, processDependencyInformation rawDepInfo bm mg)
655652

656653
-- This is factored out so it can be directly called from the GetModIface
657654
-- rule. Directly calling this rule means that on the initial load we can
@@ -660,15 +657,14 @@ dependencyInfoForFiles fs = do
660657
typeCheckRuleDefinition
661658
:: HscEnv
662659
-> ParsedModule
663-
-> NormalizedFilePath
664660
-> Action (IdeResult TcModuleResult)
665-
typeCheckRuleDefinition hsc pm fp = do
661+
typeCheckRuleDefinition hsc pm = do
666662
IdeOptions { optDefer = defer } <- getIdeOptions
667663

668664
unlift <- askUnliftIO
669665
let dets = TypecheckHelpers
670666
{ getLinkables = unliftIO unlift . uses_ GetLinkable
671-
, getModuleGraph = unliftIO unlift $ useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph fp
667+
, getModuleGraph = unliftIO unlift $ useNoFile_ GetModuleGraph
672668
}
673669
addUsageDependencies $ liftIO $
674670
typecheckModule defer hsc dets pm
@@ -766,10 +762,9 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
766762
depSessions <- map hscEnv <$> uses_ (GhcSessionDeps_ fullModSummary) deps
767763
ifaces <- uses_ GetModIface deps
768764
let inLoadOrder = map (\HiFileResult{..} -> HomeModInfo hirModIface hirModDetails emptyHomeModInfoLinkable) ifaces
769-
de <- useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph file
770765
mg <- do
771766
if fullModuleGraph
772-
then return $ depModuleGraph de
767+
then depModuleGraph <$> useNoFile_ GetModuleGraph
773768
else do
774769
let mgs = map hsc_mod_graph depSessions
775770
-- On GHC 9.4+, the module graph contains not only ModSummary's but each `ModuleNode` in the graph
@@ -782,6 +777,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
782777
nubOrdOn mkNodeKey (ModuleNode final_deps ms : concatMap mgModSummaries' mgs)
783778
liftIO $ evaluate $ liftRnf rwhnf module_graph_nodes
784779
return $ mkModuleGraph module_graph_nodes
780+
de <- useNoFile_ GetModuleGraph
785781
session' <- liftIO $ mergeEnvs hsc mg de ms inLoadOrder depSessions
786782

787783
-- Here we avoid a call to to `newHscEnvEqWithImportPaths`, which creates a new
@@ -811,7 +807,7 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco
811807
, old_value = m_old
812808
, get_file_version = use GetModificationTime_{missingFileDiagnostics = False}
813809
, get_linkable_hashes = \fs -> map (snd . fromJust . hirCoreFp) <$> uses_ GetModIface fs
814-
, get_module_graph = useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph f
810+
, get_module_graph = useNoFile_ GetModuleGraph
815811
, regenerate = regenerateHiFile session f ms
816812
}
817813
hsc_env' <- setFileCacheHook (hscEnv session)
@@ -990,7 +986,7 @@ regenerateHiFile sess f ms compNeeded = do
990986
Just pm -> do
991987
-- Invoke typechecking directly to update it without incurring a dependency
992988
-- on the parsed module and the typecheck rules
993-
(diags', mtmr) <- typeCheckRuleDefinition hsc pm f
989+
(diags', mtmr) <- typeCheckRuleDefinition hsc pm
994990
case mtmr of
995991
Nothing -> pure (diags', Nothing)
996992
Just tmr -> do
@@ -1148,7 +1144,7 @@ needsCompilationRule file
11481144
| "boot" `isSuffixOf` fromNormalizedFilePath file =
11491145
pure (Just $ encodeLinkableType Nothing, Just Nothing)
11501146
needsCompilationRule file = do
1151-
graph <- useWithSeparateFingerprintRule GetModuleGraphImmediateReverseDepsFingerprints GetModuleGraph file
1147+
graph <- useNoFile GetModuleGraph
11521148
res <- case graph of
11531149
-- Treat as False if some reverse dependency header fails to parse
11541150
Nothing -> pure Nothing
@@ -1260,19 +1256,6 @@ mainRule recorder RulesConfig{..} = do
12601256
persistentDocMapRule
12611257
persistentImportMapRule
12621258
getLinkableRule recorder
1263-
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModuleGraphTransDepsFingerprints file -> do
1264-
di <- useNoFile_ GetModuleGraph
1265-
let finger = lookupFingerprint file di (depTransDepsFingerprints di)
1266-
return (fingerprintToBS <$> finger, ([], finger))
1267-
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModuleGraphTransReverseDepsFingerprints file -> do
1268-
di <- useNoFile_ GetModuleGraph
1269-
let finger = lookupFingerprint file di (depTransReverseDepsFingerprints di)
1270-
return (fingerprintToBS <$> finger, ([], finger))
1271-
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModuleGraphImmediateReverseDepsFingerprints file -> do
1272-
di <- useNoFile_ GetModuleGraph
1273-
let finger = lookupFingerprint file di (depImmediateReverseDepsFingerprints di)
1274-
return (fingerprintToBS <$> finger, ([], finger))
1275-
12761259

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

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

Lines changed: 0 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -33,8 +33,6 @@ module Development.IDE.Core.Shake(
3333
shakeEnqueue,
3434
newSession,
3535
use, useNoFile, uses, useWithStaleFast, useWithStaleFast', delayedAction,
36-
useWithSeparateFingerprintRule,
37-
useWithSeparateFingerprintRule_,
3836
FastResult(..),
3937
use_, useNoFile_, uses_,
4038
useWithStale, usesWithStale,
@@ -1328,23 +1326,6 @@ usesWithStale key files = do
13281326
-- whether the rule succeeded or not.
13291327
traverse (lastValue key) files
13301328

1331-
-- we use separate fingerprint rules to trigger the rebuild of the rule
1332-
useWithSeparateFingerprintRule
1333-
:: (IdeRule k v, IdeRule k1 Fingerprint)
1334-
=> k1 -> k -> NormalizedFilePath -> Action (Maybe v)
1335-
useWithSeparateFingerprintRule fingerKey key file = do
1336-
_ <- use fingerKey file
1337-
useWithoutDependency key emptyFilePath
1338-
1339-
-- we use separate fingerprint rules to trigger the rebuild of the rule
1340-
useWithSeparateFingerprintRule_
1341-
:: (IdeRule k v, IdeRule k1 Fingerprint)
1342-
=> k1 -> k -> NormalizedFilePath -> Action v
1343-
useWithSeparateFingerprintRule_ fingerKey key file = do
1344-
useWithSeparateFingerprintRule fingerKey key file >>= \case
1345-
Just v -> return v
1346-
Nothing -> liftIO $ throwIO $ BadDependency (show key)
1347-
13481329
useWithoutDependency :: IdeRule k v
13491330
=> k -> NormalizedFilePath -> Action (Maybe v)
13501331
useWithoutDependency key file =

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

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

3534
import Control.DeepSeq
@@ -50,8 +49,6 @@ import qualified Data.List.NonEmpty as NonEmpty
5049
import Data.Maybe
5150
import Data.Tuple.Extra hiding (first, second)
5251
import Development.IDE.GHC.Compat
53-
import Development.IDE.GHC.Compat.Util (Fingerprint)
54-
import qualified Development.IDE.GHC.Compat.Util as Util
5552
import Development.IDE.GHC.Orphans ()
5653
import Development.IDE.Import.FindImports (ArtifactsLocation (..))
5754
import Development.IDE.Types.Diagnostics
@@ -139,35 +136,23 @@ data RawDependencyInformation = RawDependencyInformation
139136

140137
data DependencyInformation =
141138
DependencyInformation
142-
{ depErrorNodes :: !(FilePathIdMap (NonEmpty NodeError))
139+
{ depErrorNodes :: !(FilePathIdMap (NonEmpty NodeError))
143140
-- ^ Nodes that cannot be processed correctly.
144-
, depModules :: !(FilePathIdMap ShowableModule)
145-
, depModuleDeps :: !(FilePathIdMap FilePathIdSet)
141+
, depModules :: !(FilePathIdMap ShowableModule)
142+
, depModuleDeps :: !(FilePathIdMap FilePathIdSet)
146143
-- ^ For a non-error node, this contains the set of module immediate dependencies
147144
-- in the same package.
148-
, depReverseModuleDeps :: !(IntMap IntSet)
145+
, depReverseModuleDeps :: !(IntMap IntSet)
149146
-- ^ Contains a reverse mapping from a module to all those that immediately depend on it.
150-
, depPathIdMap :: !PathIdMap
147+
, depPathIdMap :: !PathIdMap
151148
-- ^ Map from FilePath to FilePathId
152-
, depBootMap :: !BootIdMap
149+
, depBootMap :: !BootIdMap
153150
-- ^ Map from hs-boot file to the corresponding hs file
154-
, depModuleFiles :: !(ShowableModuleEnv FilePathId)
151+
, depModuleFiles :: !(ShowableModuleEnv FilePathId)
155152
-- ^ Map from Module to the corresponding non-boot hs file
156-
, depModuleGraph :: !ModuleGraph
157-
, depTransDepsFingerprints :: !(FilePathIdMap Fingerprint)
158-
-- ^ Map from Module to fingerprint of the transitive dependencies of the module.
159-
, depTransReverseDepsFingerprints :: !(FilePathIdMap Fingerprint)
160-
-- ^ Map from FilePathId to the fingerprint of the transitive reverse dependencies of the module.
161-
, depImmediateReverseDepsFingerprints :: !(FilePathIdMap Fingerprint)
162-
-- ^ Map from FilePathId to the fingerprint of the immediate reverse dependencies of the module.
153+
, depModuleGraph :: !ModuleGraph
163154
} deriving (Show, Generic)
164155

165-
lookupFingerprint :: NormalizedFilePath -> DependencyInformation -> FilePathIdMap Fingerprint -> Maybe Fingerprint
166-
lookupFingerprint fileId DependencyInformation {..} depFingerprintMap =
167-
do
168-
FilePathId cur_id <- lookupPathToId depPathIdMap fileId
169-
IntMap.lookup cur_id depFingerprintMap
170-
171156
newtype ShowableModule =
172157
ShowableModule {showableModule :: Module}
173158
deriving NFData
@@ -243,8 +228,8 @@ instance Semigroup NodeResult where
243228
SuccessNode _ <> ErrorNode errs = ErrorNode errs
244229
SuccessNode a <> SuccessNode _ = SuccessNode a
245230

246-
processDependencyInformation :: RawDependencyInformation -> BootIdMap -> ModuleGraph -> FilePathIdMap Fingerprint -> DependencyInformation
247-
processDependencyInformation RawDependencyInformation{..} rawBootMap mg shallowFingerMap =
231+
processDependencyInformation :: RawDependencyInformation -> BootIdMap -> ModuleGraph -> DependencyInformation
232+
processDependencyInformation RawDependencyInformation{..} rawBootMap mg =
248233
DependencyInformation
249234
{ depErrorNodes = IntMap.fromList errorNodes
250235
, depModuleDeps = moduleDeps
@@ -254,9 +239,6 @@ processDependencyInformation RawDependencyInformation{..} rawBootMap mg shallowF
254239
, depBootMap = rawBootMap
255240
, depModuleFiles = ShowableModuleEnv reverseModuleMap
256241
, depModuleGraph = mg
257-
, depTransDepsFingerprints = buildTransDepsFingerprintMap moduleDeps shallowFingerMap
258-
, depTransReverseDepsFingerprints = buildTransDepsFingerprintMap reverseModuleDeps shallowFingerMap
259-
, depImmediateReverseDepsFingerprints = buildImmediateDepsFingerprintMap reverseModuleDeps shallowFingerMap
260242
}
261243
where resultGraph = buildResultGraph rawImports
262244
(errorNodes, successNodes) = partitionNodeResults $ IntMap.toList resultGraph
@@ -416,44 +398,3 @@ instance NFData NamedModuleDep where
416398

417399
instance Show NamedModuleDep where
418400
show NamedModuleDep{..} = show nmdFilePath
419-
420-
421-
buildImmediateDepsFingerprintMap :: FilePathIdMap FilePathIdSet -> FilePathIdMap Fingerprint -> FilePathIdMap Fingerprint
422-
buildImmediateDepsFingerprintMap modulesDeps shallowFingers =
423-
IntMap.fromList
424-
$ map
425-
( \k ->
426-
( k,
427-
Util.fingerprintFingerprints $
428-
map
429-
(shallowFingers IntMap.!)
430-
(k : IntSet.toList (IntMap.findWithDefault IntSet.empty k modulesDeps))
431-
)
432-
)
433-
$ IntMap.keys shallowFingers
434-
435-
-- | Build a map from file path to its full fingerprint.
436-
-- The fingerprint is depend on both the fingerprints of the file and all its dependencies.
437-
-- This is used to determine if a file has changed and needs to be reloaded.
438-
buildTransDepsFingerprintMap :: FilePathIdMap FilePathIdSet -> FilePathIdMap Fingerprint -> FilePathIdMap Fingerprint
439-
buildTransDepsFingerprintMap modulesDeps shallowFingers = go keys IntMap.empty
440-
where
441-
keys = IntMap.keys shallowFingers
442-
go :: [IntSet.Key] -> FilePathIdMap Fingerprint -> FilePathIdMap Fingerprint
443-
go keys acc =
444-
case keys of
445-
[] -> acc
446-
k : ks ->
447-
if IntMap.member k acc
448-
-- already in the map, so we can skip
449-
then go ks acc
450-
-- not in the map, so we need to add it
451-
else
452-
let -- get the dependencies of the current key
453-
deps = IntSet.toList $ IntMap.findWithDefault IntSet.empty k modulesDeps
454-
-- add fingerprints of the dependencies to the accumulator
455-
depFingerprints = go deps acc
456-
-- combine the fingerprints of the dependencies with the current key
457-
combinedFingerprints = Util.fingerprintFingerprints $ shallowFingers IntMap.! k : map (depFingerprints IntMap.!) deps
458-
in -- add the combined fingerprints to the accumulator
459-
go ks (IntMap.insert k combinedFingerprints depFingerprints)

0 commit comments

Comments
 (0)