Skip to content

Commit bebead5

Browse files
committed
maximize sharing by creating a finger print rule and query result from GetModuleGraph
1 parent 8afa778 commit bebead5

File tree

5 files changed

+38
-18
lines changed

5 files changed

+38
-18
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 <$> use_ GetFileModuleGraph nfp
267+
revs <- transitiveReverseDependencies nfp <$> useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint 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: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -74,8 +74,9 @@ type instance RuleResult GetParsedModuleWithComments = ParsedModule
7474

7575
type instance RuleResult GetModuleGraph = DependencyInformation
7676

77-
-- same as GetModuleGraph but only rebuilds if the target file deps changes
78-
type instance RuleResult GetFileModuleGraph = DependencyInformation
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 GetFileModuleGraphFingerprint = Fingerprint
7980

8081
data GetKnownTargets = GetKnownTargets
8182
deriving (Show, Generic, Eq, Ord)
@@ -420,10 +421,10 @@ data GetModuleGraph = GetModuleGraph
420421
instance Hashable GetModuleGraph
421422
instance NFData GetModuleGraph
422423

423-
data GetFileModuleGraph = GetFileModuleGraph
424+
data GetFileModuleGraphFingerprint = GetFileModuleGraphFingerprint
424425
deriving (Eq, Show, Generic)
425-
instance Hashable GetFileModuleGraph
426-
instance NFData GetFileModuleGraph
426+
instance Hashable GetFileModuleGraphFingerprint
427+
instance NFData GetFileModuleGraphFingerprint
427428

428429
data ReportImportCycles = ReportImportCycles
429430
deriving (Eq, Show, Generic)

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

Lines changed: 8 additions & 8 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{..} <- use_ GetFileModuleGraph file
475+
DependencyInformation{..} <- useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint 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 []
@@ -630,9 +630,9 @@ getModuleGraphRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake rec
630630

631631
getModuleGraphSingleFileRule :: Recorder (WithPriority Log) -> Rules ()
632632
getModuleGraphSingleFileRule recorder =
633-
defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetFileModuleGraph file -> do
633+
defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \GetFileModuleGraphFingerprint file -> do
634634
di <- useNoFile_ GetModuleGraph
635-
return (fingerprintToBS <$> lookupFingerprint file di, ([], Just di))
635+
return $ lookupFingerprint file di
636636

637637
dependencyInfoForFiles :: [NormalizedFilePath] -> Action (BS.ByteString, DependencyInformation)
638638
dependencyInfoForFiles fs = do
@@ -669,7 +669,7 @@ typeCheckRuleDefinition hsc pm fp = do
669669
unlift <- askUnliftIO
670670
let dets = TypecheckHelpers
671671
{ getLinkables = unliftIO unlift . uses_ GetLinkable
672-
, getModuleGraph = unliftIO unlift $ use_ GetFileModuleGraph fp
672+
, getModuleGraph = unliftIO unlift $ useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph fp
673673
}
674674
addUsageDependencies $ liftIO $
675675
typecheckModule defer hsc dets pm
@@ -768,7 +768,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
768768
let inLoadOrder = map (\HiFileResult{..} -> HomeModInfo hirModIface hirModDetails emptyHomeModInfoLinkable) ifaces
769769
mg <- do
770770
if fullModuleGraph
771-
then depModuleGraph <$> use_ GetFileModuleGraph file
771+
then depModuleGraph <$> useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph file
772772
else do
773773
let mgs = map hsc_mod_graph depSessions
774774
-- On GHC 9.4+, the module graph contains not only ModSummary's but each `ModuleNode` in the graph
@@ -781,7 +781,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
781781
nubOrdOn mkNodeKey (ModuleNode final_deps ms : concatMap mgModSummaries' mgs)
782782
liftIO $ evaluate $ liftRnf rwhnf module_graph_nodes
783783
return $ mkModuleGraph module_graph_nodes
784-
de <- use_ GetFileModuleGraph file
784+
de <- useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph file
785785
session' <- liftIO $ mergeEnvs hsc mg de ms inLoadOrder depSessions
786786

787787
-- Here we avoid a call to to `newHscEnvEqWithImportPaths`, which creates a new
@@ -811,7 +811,7 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco
811811
, old_value = m_old
812812
, get_file_version = use GetModificationTime_{missingFileDiagnostics = False}
813813
, get_linkable_hashes = \fs -> map (snd . fromJust . hirCoreFp) <$> uses_ GetModIface fs
814-
, get_module_graph = use_ GetFileModuleGraph f
814+
, get_module_graph = useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint GetModuleGraph f
815815
, regenerate = regenerateHiFile session f ms
816816
}
817817
hsc_env' <- setFileCacheHook (hscEnv session)
@@ -1145,7 +1145,7 @@ needsCompilationRule file
11451145
| "boot" `isSuffixOf` fromNormalizedFilePath file =
11461146
pure (Just $ encodeLinkableType Nothing, Just Nothing)
11471147
needsCompilationRule file = do
1148-
graph <- use GetFileModuleGraph file
1148+
graph <- useWithSeparateFingerprintRule GetFileModuleGraphFingerprint GetModuleGraph file
11491149
res <- case graph of
11501150
-- Treat as False if some reverse dependency header fails to parse
11511151
Nothing -> pure Nothing

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 =

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

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ import qualified Data.Text.Utf16.Rope.Mixed as Rope
4444
import Development.IDE.Core.FileStore (getUriContents, setSomethingModified)
4545
import Development.IDE.Core.Rules (IdeState,
4646
runAction)
47-
import Development.IDE.Core.Shake (use_, uses_, VFSModified (VFSUnmodified))
47+
import Development.IDE.Core.Shake (use_, uses_, VFSModified (VFSUnmodified), useWithSeparateFingerprintRule_)
4848
import Development.IDE.GHC.Compat hiding (typeKind,
4949
unitState)
5050
import Development.IDE.GHC.Compat.Util (OverridingBool (..))
@@ -72,12 +72,12 @@ import GHC (ClsInst,
7272

7373
import Development.IDE.Core.RuleTypes (GetLinkable (GetLinkable),
7474
GetModSummary (GetModSummary),
75-
GetFileModuleGraph (GetFileModuleGraph),
75+
GetFileModuleGraphFingerprint (GetFileModuleGraphFingerprint),
7676
GhcSessionDeps (GhcSessionDeps),
7777
ModSummaryResult (msrModSummary),
7878
LinkableResult (linkableHomeMod),
7979
TypeCheck (..),
80-
tmrTypechecked, GetFileModuleGraph(..))
80+
tmrTypechecked, GetFileModuleGraphFingerprint(..), 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 <$> use_ GetFileModuleGraph nfp <*> pure nfp
256+
linkables_needed <- transitiveDeps <$> useWithSeparateFingerprintRule_ GetFileModuleGraphFingerprint 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)