@@ -472,7 +472,7 @@ rawDependencyInformation fs = do
472472reportImportCyclesRule :: Recorder (WithPriority Log ) -> Rules ()
473473reportImportCyclesRule 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
613613knownFilesRule :: Recorder (WithPriority Log ) -> Rules ()
614614knownFilesRule 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+
631637dependencyInfoForFiles :: [NormalizedFilePath ] -> Action (BS. ByteString , DependencyInformation )
632638dependencyInfoForFiles 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
652661typeCheckRuleDefinition
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
0 commit comments