Skip to content

Commit 4cb5a70

Browse files
authored
Merge branch 'master' into batch-load-multi-read
2 parents 4a78e6e + 997a426 commit 4cb5a70

File tree

7 files changed

+147
-32
lines changed

7 files changed

+147
-32
lines changed

flake.nix

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -61,6 +61,8 @@
6161
pkgs.haskellPackages.cabal-install
6262
# Dependencies needed to build some parts of Hackage
6363
gmp zlib ncurses
64+
# for compatibility of curl with provided gcc
65+
curl
6466
# Changelog tooling
6567
(gen-hls-changelogs pkgs.haskellPackages)
6668
# For the documentation

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 <$> 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: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -74,6 +74,12 @@ type instance RuleResult GetParsedModuleWithComments = ParsedModule
7474

7575
type instance RuleResult GetModuleGraph = DependencyInformation
7676

77+
-- | it only compute the fingerprint of the module graph for a file and its dependencies
78+
-- we need this to trigger recompilation when the sub module graph for a file changes
79+
type instance RuleResult GetModuleGraphTransDepsFingerprints = Fingerprint
80+
type instance RuleResult GetModuleGraphTransReverseDepsFingerprints = Fingerprint
81+
type instance RuleResult GetModuleGraphImmediateReverseDepsFingerprints = Fingerprint
82+
7783
data GetKnownTargets = GetKnownTargets
7884
deriving (Show, Generic, Eq, Ord)
7985
instance Hashable GetKnownTargets
@@ -417,6 +423,21 @@ data GetModuleGraph = GetModuleGraph
417423
instance Hashable GetModuleGraph
418424
instance NFData GetModuleGraph
419425

426+
data GetModuleGraphTransDepsFingerprints = GetModuleGraphTransDepsFingerprints
427+
deriving (Eq, Show, Generic)
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
440+
420441
data ReportImportCycles = ReportImportCycles
421442
deriving (Eq, Show, Generic)
422443
instance Hashable ReportImportCycles

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

Lines changed: 27 additions & 10 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{..} <- 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 []
@@ -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
@@ -643,7 +643,10 @@ dependencyInfoForFiles fs = do
643643
go (Just ms) _ = Just $ ModuleNode [] ms
644644
go _ _ = Nothing
645645
mg = mkModuleGraph mns
646-
pure (fingerprintToBS $ Util.fingerprintFingerprints $ map (maybe fingerprint0 msrFingerprint) msrs, processDependencyInformation rawDepInfo bm mg)
646+
let shallowFingers = IntMap.fromList $ foldr' (\(i, m) acc -> case m of
647+
Just x -> (getFilePathId i,msrFingerprint x):acc
648+
Nothing -> acc) [] $ zip _all_ids msrs
649+
pure (fingerprintToBS $ Util.fingerprintFingerprints $ map (maybe fingerprint0 msrFingerprint) msrs, processDependencyInformation rawDepInfo bm mg shallowFingers)
647650

648651
-- This is factored out so it can be directly called from the GetModIface
649652
-- rule. Directly calling this rule means that on the initial load we can
@@ -652,14 +655,15 @@ dependencyInfoForFiles fs = do
652655
typeCheckRuleDefinition
653656
:: HscEnv
654657
-> ParsedModule
658+
-> NormalizedFilePath
655659
-> Action (IdeResult TcModuleResult)
656-
typeCheckRuleDefinition hsc pm = do
660+
typeCheckRuleDefinition hsc pm fp = do
657661
IdeOptions { optDefer = defer } <- getIdeOptions
658662

659663
unlift <- askUnliftIO
660664
let dets = TypecheckHelpers
661665
{ getLinkables = unliftIO unlift . uses_ GetLinkable
662-
, getModuleGraph = unliftIO unlift $ useNoFile_ GetModuleGraph
666+
, getModuleGraph = unliftIO unlift $ useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph fp
663667
}
664668
addUsageDependencies $ liftIO $
665669
typecheckModule defer hsc dets pm
@@ -756,9 +760,10 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
756760
depSessions <- map hscEnv <$> uses_ (GhcSessionDeps_ fullModSummary) deps
757761
ifaces <- uses_ GetModIface deps
758762
let inLoadOrder = map (\HiFileResult{..} -> HomeModInfo hirModIface hirModDetails emptyHomeModInfoLinkable) ifaces
763+
de <- useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph file
759764
mg <- do
760765
if fullModuleGraph
761-
then depModuleGraph <$> useNoFile_ GetModuleGraph
766+
then return $ depModuleGraph de
762767
else do
763768
let mgs = map hsc_mod_graph depSessions
764769
-- On GHC 9.4+, the module graph contains not only ModSummary's but each `ModuleNode` in the graph
@@ -771,7 +776,6 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
771776
nubOrdOn mkNodeKey (ModuleNode final_deps ms : concatMap mgModSummaries' mgs)
772777
liftIO $ evaluate $ liftRnf rwhnf module_graph_nodes
773778
return $ mkModuleGraph module_graph_nodes
774-
de <- useNoFile_ GetModuleGraph
775779
session' <- liftIO $ mergeEnvs hsc mg de ms inLoadOrder depSessions
776780

777781
-- Here we avoid a call to to `newHscEnvEqWithImportPaths`, which creates a new
@@ -801,7 +805,7 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco
801805
, old_value = m_old
802806
, get_file_version = use GetModificationTime_{missingFileDiagnostics = False}
803807
, get_linkable_hashes = \fs -> map (snd . fromJust . hirCoreFp) <$> uses_ GetModIface fs
804-
, get_module_graph = useNoFile_ GetModuleGraph
808+
, get_module_graph = useWithSeparateFingerprintRule_ GetModuleGraphTransDepsFingerprints GetModuleGraph f
805809
, regenerate = regenerateHiFile session f ms
806810
}
807811
hsc_env' <- setFileCacheHook (hscEnv session)
@@ -977,7 +981,7 @@ regenerateHiFile sess f ms compNeeded = do
977981
Just pm -> do
978982
-- Invoke typechecking directly to update it without incurring a dependency
979983
-- on the parsed module and the typecheck rules
980-
(diags', mtmr) <- typeCheckRuleDefinition hsc pm
984+
(diags', mtmr) <- typeCheckRuleDefinition hsc pm f
981985
case mtmr of
982986
Nothing -> pure (diags', Nothing)
983987
Just tmr -> do
@@ -1135,7 +1139,7 @@ needsCompilationRule file
11351139
| "boot" `isSuffixOf` fromNormalizedFilePath file =
11361140
pure (Just $ encodeLinkableType Nothing, Just Nothing)
11371141
needsCompilationRule file = do
1138-
graph <- useNoFile GetModuleGraph
1142+
graph <- useWithSeparateFingerprintRule GetModuleGraphImmediateReverseDepsFingerprints GetModuleGraph file
11391143
res <- case graph of
11401144
-- Treat as False if some reverse dependency header fails to parse
11411145
Nothing -> pure Nothing
@@ -1247,6 +1251,19 @@ mainRule recorder RulesConfig{..} = do
12471251
persistentDocMapRule
12481252
persistentImportMapRule
12491253
getLinkableRule recorder
1254+
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModuleGraphTransDepsFingerprints file -> do
1255+
di <- useNoFile_ GetModuleGraph
1256+
let finger = lookupFingerprint file di (depTransDepsFingerprints di)
1257+
return (fingerprintToBS <$> finger, ([], finger))
1258+
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModuleGraphTransReverseDepsFingerprints file -> do
1259+
di <- useNoFile_ GetModuleGraph
1260+
let finger = lookupFingerprint file di (depTransReverseDepsFingerprints di)
1261+
return (fingerprintToBS <$> finger, ([], finger))
1262+
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModuleGraphImmediateReverseDepsFingerprints file -> do
1263+
di <- useNoFile_ GetModuleGraph
1264+
let finger = lookupFingerprint file di (depImmediateReverseDepsFingerprints di)
1265+
return (fingerprintToBS <$> finger, ([], finger))
1266+
12501267

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

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

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,8 @@ module Development.IDE.Core.Shake(
3131
shakeEnqueue,
3232
newSession,
3333
use, useNoFile, uses, useWithStaleFast, useWithStaleFast', delayedAction,
34+
useWithSeparateFingerprintRule,
35+
useWithSeparateFingerprintRule_,
3436
FastResult(..),
3537
use_, useNoFile_, uses_,
3638
useWithStale, usesWithStale,
@@ -1148,6 +1150,23 @@ usesWithStale key files = do
11481150
-- whether the rule succeeded or not.
11491151
traverse (lastValue key) files
11501152

1153+
-- we use separate fingerprint rules to trigger the rebuild of the rule
1154+
useWithSeparateFingerprintRule
1155+
:: (IdeRule k v, IdeRule k1 Fingerprint)
1156+
=> k1 -> k -> NormalizedFilePath -> Action (Maybe v)
1157+
useWithSeparateFingerprintRule fingerKey key file = do
1158+
_ <- use fingerKey file
1159+
useWithoutDependency key emptyFilePath
1160+
1161+
-- we use separate fingerprint rules to trigger the rebuild of the rule
1162+
useWithSeparateFingerprintRule_
1163+
:: (IdeRule k v, IdeRule k1 Fingerprint)
1164+
=> k1 -> k -> NormalizedFilePath -> Action v
1165+
useWithSeparateFingerprintRule_ fingerKey key file = do
1166+
useWithSeparateFingerprintRule fingerKey key file >>= \case
1167+
Just v -> return v
1168+
Nothing -> liftIO $ throwIO $ BadDependency (show key)
1169+
11511170
useWithoutDependency :: IdeRule k v
11521171
=> k -> NormalizedFilePath -> Action (Maybe v)
11531172
useWithoutDependency key file =

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

Lines changed: 69 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,35 @@ 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+
, 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.
154163
} deriving (Show, Generic)
155164

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+
156171
newtype ShowableModule =
157172
ShowableModule {showableModule :: Module}
158173
deriving NFData
@@ -228,8 +243,8 @@ instance Semigroup NodeResult where
228243
SuccessNode _ <> ErrorNode errs = ErrorNode errs
229244
SuccessNode a <> SuccessNode _ = SuccessNode a
230245

231-
processDependencyInformation :: RawDependencyInformation -> BootIdMap -> ModuleGraph -> DependencyInformation
232-
processDependencyInformation RawDependencyInformation{..} rawBootMap mg =
246+
processDependencyInformation :: RawDependencyInformation -> BootIdMap -> ModuleGraph -> FilePathIdMap Fingerprint -> DependencyInformation
247+
processDependencyInformation RawDependencyInformation{..} rawBootMap mg shallowFingerMap =
233248
DependencyInformation
234249
{ depErrorNodes = IntMap.fromList errorNodes
235250
, depModuleDeps = moduleDeps
@@ -239,6 +254,9 @@ processDependencyInformation RawDependencyInformation{..} rawBootMap mg =
239254
, depBootMap = rawBootMap
240255
, depModuleFiles = ShowableModuleEnv reverseModuleMap
241256
, depModuleGraph = mg
257+
, depTransDepsFingerprints = buildTransDepsFingerprintMap moduleDeps shallowFingerMap
258+
, depTransReverseDepsFingerprints = buildTransDepsFingerprintMap reverseModuleDeps shallowFingerMap
259+
, depImmediateReverseDepsFingerprints = buildImmediateDepsFingerprintMap reverseModuleDeps shallowFingerMap
242260
}
243261
where resultGraph = buildResultGraph rawImports
244262
(errorNodes, successNodes) = partitionNodeResults $ IntMap.toList resultGraph
@@ -398,3 +416,44 @@ instance NFData NamedModuleDep where
398416

399417
instance Show NamedModuleDep where
400418
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)