@@ -477,7 +477,7 @@ rawDependencyInformation fs = do
477477reportImportCyclesRule :: Recorder (WithPriority Log ) -> Rules ()
478478reportImportCyclesRule 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
618618knownFilesRule :: Recorder (WithPriority Log ) -> Rules ()
619619knownFilesRule 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
660657typeCheckRuleDefinition
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 )
11501146needsCompilationRule 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
12781261getHieFile :: NormalizedFilePath -> Action (Maybe HieFile )
0 commit comments