@@ -14,6 +14,10 @@ module Development.IDE.Core.Rules(
14
14
IdeState , GetParsedModule (.. ), TransitiveDependencies (.. ),
15
15
Priority (.. ), GhcSessionIO (.. ), GetClientSettings (.. ),
16
16
-- * Functions
17
+ --
18
+ --
19
+ --
20
+ --
17
21
priorityTypeCheck ,
18
22
priorityGenerateCore ,
19
23
priorityFilesOfInterest ,
@@ -23,7 +27,6 @@ module Development.IDE.Core.Rules(
23
27
defineEarlyCutOffNoFile ,
24
28
mainRule ,
25
29
RulesConfig (.. ),
26
- getDependencies ,
27
30
getParsedModule ,
28
31
getParsedModuleWithComments ,
29
32
getClientConfigAction ,
@@ -155,6 +158,7 @@ import qualified Development.IDE.Types.Shake as Shake
155
158
import Development.IDE.GHC.CoreFile
156
159
import Data.Time.Clock.POSIX (posixSecondsToUTCTime )
157
160
import Control.Monad.IO.Unlift
161
+ import qualified Data.IntMap as IM
158
162
#if MIN_VERSION_ghc(9,3,0)
159
163
import GHC.Unit.Module.Graph
160
164
import GHC.Unit.Env
@@ -204,12 +208,6 @@ toIdeResult = either (, Nothing) (([],) . Just)
204
208
------------------------------------------------------------
205
209
-- Exposed API
206
210
------------------------------------------------------------
207
- -- | Get all transitive file dependencies of a given module.
208
- -- Does not include the file itself.
209
- getDependencies :: NormalizedFilePath -> Action (Maybe [NormalizedFilePath ])
210
- getDependencies file =
211
- fmap transitiveModuleDeps . (`transitiveDeps` file) <$> useNoFile_ GetModuleGraph
212
-
213
211
getSourceFileSource :: NormalizedFilePath -> Action BS. ByteString
214
212
getSourceFileSource nfp = do
215
213
(_, msource) <- getFileContents nfp
@@ -417,17 +415,17 @@ type RawDepM a = StateT (RawDependencyInformation, IntMap ArtifactsLocation) Act
417
415
execRawDepM :: Monad m => StateT (RawDependencyInformation , IntMap a1 ) m a2 -> m (RawDependencyInformation , IntMap a1 )
418
416
execRawDepM act =
419
417
execStateT act
420
- ( RawDependencyInformation IntMap. empty emptyPathIdMap IntMap. empty IntMap. empty
418
+ ( RawDependencyInformation IntMap. empty emptyPathIdMap IntMap. empty
421
419
, IntMap. empty
422
420
)
423
421
424
422
-- | Given a target file path, construct the raw dependency results by following
425
423
-- imports recursively.
426
- rawDependencyInformation :: [NormalizedFilePath ] -> Action RawDependencyInformation
424
+ rawDependencyInformation :: [NormalizedFilePath ] -> Action ( RawDependencyInformation , BootIdMap )
427
425
rawDependencyInformation fs = do
428
426
(rdi, ss) <- execRawDepM (goPlural fs)
429
427
let bm = IntMap. foldrWithKey (updateBootMap rdi) IntMap. empty ss
430
- return (rdi { rawBootMap = bm } )
428
+ return (rdi, bm )
431
429
where
432
430
goPlural ff = do
433
431
mss <- lift $ (fmap . fmap ) msrModSummary <$> uses GetModSummaryWithoutTimestamps ff
@@ -446,9 +444,9 @@ rawDependencyInformation fs = do
446
444
fId <- getFreshFid al
447
445
-- Record this module and its location
448
446
whenJust msum $ \ ms ->
449
- modifyRawDepInfo (\ rd -> rd { rawModuleNameMap = IntMap. insert (getFilePathId fId)
450
- (ShowableModuleName (moduleName $ ms_mod ms) )
451
- (rawModuleNameMap rd)})
447
+ modifyRawDepInfo (\ rd -> rd { rawModuleMap = IntMap. insert (getFilePathId fId)
448
+ (ShowableModule $ ms_mod ms)
449
+ (rawModuleMap rd)})
452
450
-- Adding an edge to the bootmap so we can make sure to
453
451
-- insert boot nodes before the real files.
454
452
addBootMap al fId
@@ -670,8 +668,30 @@ knownFilesRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake recorde
670
668
getModuleGraphRule :: Recorder (WithPriority Log ) -> Rules ()
671
669
getModuleGraphRule recorder = defineNoFile (cmapWithPrio LogShake recorder) $ \ GetModuleGraph -> do
672
670
fs <- toKnownFiles <$> useNoFile_ GetKnownTargets
673
- rawDepInfo <- rawDependencyInformation (HashSet. toList fs)
674
- pure $ processDependencyInformation rawDepInfo
671
+ (rawDepInfo, bm) <- rawDependencyInformation (HashSet. toList fs)
672
+ let (all_fs, _all_ids) = unzip $ HM. toList $ pathToIdMap $ rawPathIdMap rawDepInfo
673
+ mss <- map (fmap msrModSummary) <$> uses GetModSummaryWithoutTimestamps all_fs
674
+ #if MIN_VERSION_ghc(9,3,0)
675
+ let deps = map (\ i -> IM. lookup (getFilePathId i) (rawImports rawDepInfo)) _all_ids
676
+ nodeKeys = IM. fromList $ catMaybes $ zipWith (\ fi mms -> (getFilePathId fi,) . NodeKey_Module . msKey <$> mms) _all_ids mss
677
+ mns = catMaybes $ zipWith go mss deps
678
+ go (Just ms) (Just (Right (ModuleImports xs))) = Just $ ModuleNode this_dep_keys ms
679
+ where this_dep_ids = mapMaybe snd xs
680
+ this_dep_keys = mapMaybe (\ fi -> IM. lookup (getFilePathId fi) nodeKeys) this_dep_ids
681
+ go (Just ms) _ = Just $ ModuleNode [] ms
682
+ go _ _ = Nothing
683
+ mg = mkModuleGraph mns
684
+ #else
685
+ let mg = mkModuleGraph $
686
+ #if MIN_VERSION_ghc(9,2,0)
687
+ -- We don't do any instantiation for backpack at this point of time, so it is OK to use
688
+ -- 'extendModSummaryNoDeps'.
689
+ -- This may have to change in the future.
690
+ map extendModSummaryNoDeps $
691
+ #endif
692
+ (catMaybes mss)
693
+ #endif
694
+ pure $ processDependencyInformation rawDepInfo bm mg
675
695
676
696
-- This is factored out so it can be directly called from the GetModIface
677
697
-- rule. Directly calling this rule means that on the initial load we can
@@ -772,19 +792,8 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
772
792
depSessions <- map hscEnv <$> uses_ (GhcSessionDeps_ fullModSummary) deps
773
793
ifaces <- uses_ GetModIface deps
774
794
let inLoadOrder = map (\ HiFileResult {.. } -> HomeModInfo hirModIface hirModDetails Nothing ) ifaces
775
- #if MIN_VERSION_ghc(9,3,0)
776
- -- On GHC 9.4+, the module graph contains not only ModSummary's but each `ModuleNode` in the graph
777
- -- also points to all the direct descendants of the current module. To get the keys for the descendants
778
- -- we must get their `ModSummary`s
779
- ! final_deps <- do
780
- dep_mss <- map msrModSummary <$> uses_ GetModSummaryWithoutTimestamps deps
781
- -- Don't want to retain references to the entire ModSummary when just the key will do
782
- return $!! map (NodeKey_Module . msKey) dep_mss
783
- let moduleNode = (ms, final_deps)
784
- #else
785
- let moduleNode = ms
786
- #endif
787
- session' <- liftIO $ mergeEnvs hsc moduleNode inLoadOrder depSessions
795
+ mg <- depModuleGraph <$> useNoFile_ GetModuleGraph
796
+ session' <- liftIO $ mergeEnvs hsc mg ms inLoadOrder depSessions
788
797
789
798
Just <$> liftIO (newHscEnvEqWithImportPaths (envImportPaths env) session' [] )
790
799
0 commit comments