@@ -9,6 +9,7 @@ module Development.IDE.Import.DependencyInformation
99 , ModuleParseError (.. )
1010 , TransitiveDependencies (.. )
1111 , FilePathId (.. )
12+ , NamedModuleDep (.. )
1213
1314 , PathIdMap
1415 , emptyPathIdMap
@@ -17,7 +18,7 @@ module Development.IDE.Import.DependencyInformation
1718 , pathToId
1819 , idToPath
1920 , reachableModules
20-
21+ , modLocationToNormalizedFilePath
2122 , processDependencyInformation
2223 , transitiveDeps
2324 ) where
@@ -46,6 +47,7 @@ import GHC.Generics (Generic)
4647
4748import Development.IDE.Types.Diagnostics
4849import Development.IDE.Types.Location
50+ import Development.IDE.Import.FindImports (ArtifactsLocation (.. ))
4951
5052import GHC
5153import Module
@@ -67,27 +69,34 @@ newtype FilePathId = FilePathId { getFilePathId :: Int }
6769 deriving (Show , NFData , Eq , Ord )
6870
6971data PathIdMap = PathIdMap
70- { idToPathMap :: ! (IntMap NormalizedFilePath )
72+ { idToPathMap :: ! (IntMap ArtifactsLocation )
7173 , pathToIdMap :: ! (HashMap NormalizedFilePath FilePathId )
7274 }
7375 deriving (Show , Generic )
7476
7577instance NFData PathIdMap
7678
79+ modLocationToNormalizedFilePath :: ArtifactsLocation -> NormalizedFilePath
80+ modLocationToNormalizedFilePath (ArtifactsLocation loc) =
81+ case ml_hs_file loc of
82+ Just filePath -> toNormalizedFilePath filePath
83+ -- Since we craete all 'ModLocation' values via 'mkHomeModLocation'
84+ Nothing -> error " Has something changed in mkHomeModLocation?"
85+
7786emptyPathIdMap :: PathIdMap
7887emptyPathIdMap = PathIdMap IntMap. empty HMS. empty
7988
80- getPathId :: NormalizedFilePath -> PathIdMap -> (FilePathId , PathIdMap )
89+ getPathId :: ArtifactsLocation -> PathIdMap -> (FilePathId , PathIdMap )
8190getPathId path m@ PathIdMap {.. } =
82- case HMS. lookup path pathToIdMap of
91+ case HMS. lookup (modLocationToNormalizedFilePath path) pathToIdMap of
8392 Nothing ->
8493 let ! newId = FilePathId $ HMS. size pathToIdMap
8594 in (newId, insertPathId path newId m)
8695 Just id -> (id , m)
8796
88- insertPathId :: NormalizedFilePath -> FilePathId -> PathIdMap -> PathIdMap
97+ insertPathId :: ArtifactsLocation -> FilePathId -> PathIdMap -> PathIdMap
8998insertPathId path id PathIdMap {.. } =
90- PathIdMap (IntMap. insert (getFilePathId id ) path idToPathMap) (HMS. insert path id pathToIdMap)
99+ PathIdMap (IntMap. insert (getFilePathId id ) path idToPathMap) (HMS. insert (modLocationToNormalizedFilePath path) id pathToIdMap)
91100
92101insertImport :: FilePathId -> Either ModuleParseError ModuleImports -> RawDependencyInformation -> RawDependencyInformation
93102insertImport (FilePathId k) v rawDepInfo = rawDepInfo { rawImports = IntMap. insert k v (rawImports rawDepInfo) }
@@ -96,7 +105,11 @@ pathToId :: PathIdMap -> NormalizedFilePath -> FilePathId
96105pathToId PathIdMap {pathToIdMap} path = pathToIdMap HMS. ! path
97106
98107idToPath :: PathIdMap -> FilePathId -> NormalizedFilePath
99- idToPath PathIdMap {idToPathMap} (FilePathId id ) = idToPathMap IntMap. ! id
108+ idToPath pathIdMap filePathId = modLocationToNormalizedFilePath $ idToModLocation pathIdMap filePathId
109+
110+ idToModLocation :: PathIdMap -> FilePathId -> ArtifactsLocation
111+ idToModLocation PathIdMap {idToPathMap} (FilePathId id ) = idToPathMap IntMap. ! id
112+
100113
101114-- | Unprocessed results that we find by following imports recursively.
102115data RawDependencyInformation = RawDependencyInformation
@@ -112,6 +125,7 @@ data DependencyInformation =
112125 DependencyInformation
113126 { depErrorNodes :: ! (IntMap (NonEmpty NodeError ))
114127 -- ^ Nodes that cannot be processed correctly.
128+ , depModuleNames :: ! (IntMap ShowableModuleName )
115129 , depModuleDeps :: ! (IntMap IntSet )
116130 -- ^ For a non-error node, this contains the set of module immediate dependencies
117131 -- in the same package.
@@ -120,6 +134,12 @@ data DependencyInformation =
120134 , depPathIdMap :: ! PathIdMap
121135 } deriving (Show , Generic )
122136
137+ newtype ShowableModuleName =
138+ ShowableModuleName { showableModuleName :: ModuleName }
139+ deriving NFData
140+
141+ instance Show ShowableModuleName where show = moduleNameString . showableModuleName
142+
123143reachableModules :: DependencyInformation -> [NormalizedFilePath ]
124144reachableModules DependencyInformation {.. } =
125145 map (idToPath depPathIdMap . FilePathId ) $ IntMap. keys depErrorNodes <> IntMap. keys depModuleDeps
@@ -186,16 +206,24 @@ processDependencyInformation rawDepInfo@RawDependencyInformation{..} =
186206 DependencyInformation
187207 { depErrorNodes = IntMap. fromList errorNodes
188208 , depModuleDeps = moduleDeps
209+ , depModuleNames = IntMap. fromList $ coerce moduleNames
189210 , depPkgDeps = pkgDependencies rawDepInfo
190211 , depPathIdMap = rawPathIdMap
191212 }
192213 where resultGraph = buildResultGraph rawImports
193214 (errorNodes, successNodes) = partitionNodeResults $ IntMap. toList resultGraph
215+ moduleNames :: [(FilePathId , ModuleName )]
216+ moduleNames =
217+ [ (fId, modName) | (_, imports) <- successNodes, (L _ modName, fId) <- imports]
194218 successEdges :: [(FilePathId , FilePathId , [FilePathId ])]
195219 successEdges =
196- map (\ (file, imports) -> (FilePathId file, FilePathId file, map snd imports)) successNodes
220+ map
221+ (\ (file, imports) -> (FilePathId file, FilePathId file, map snd imports))
222+ successNodes
197223 moduleDeps =
198- IntMap. fromList $ map (\ (_, FilePathId v, vs) -> (v, IntSet. fromList $ coerce vs)) successEdges
224+ IntMap. fromList $
225+ map (\ (_, FilePathId v, vs) -> (v, IntSet. fromList $ coerce vs))
226+ successEdges
199227
200228-- | Given a dependency graph, buildResultGraph detects and propagates errors in that graph as follows:
201229-- 1. Mark each node that is part of an import cycle as an error node.
@@ -268,22 +296,52 @@ transitiveDeps DependencyInformation{..} file = do
268296 IntSet. delete (getFilePathId fileId) .
269297 IntSet. fromList . map (fst3 . fromVertex) .
270298 reachable g <$> toVertex (getFilePathId fileId)
271- let transitiveModuleDepIds = filter (\ v -> v `IntSet.member` reachableVs) $ map (fst3 . fromVertex) vs
299+ let transitiveModuleDepIds =
300+ filter (\ v -> v `IntSet.member` reachableVs) $ map (fst3 . fromVertex) vs
272301 let transitivePkgDeps =
273302 Set. toList $ Set. unions $
274303 map (\ f -> IntMap. findWithDefault Set. empty f depPkgDeps) $
275304 getFilePathId fileId : transitiveModuleDepIds
276- let transitiveModuleDeps = map (idToPath depPathIdMap . FilePathId ) transitiveModuleDepIds
305+ let transitiveModuleDeps =
306+ map (idToPath depPathIdMap . FilePathId ) transitiveModuleDepIds
307+ let transitiveNamedModuleDeps =
308+ [ NamedModuleDep (idToPath depPathIdMap (FilePathId fid)) mn ml
309+ | (fid, ShowableModuleName mn) <- IntMap. toList depModuleNames
310+ , let ArtifactsLocation ml = idToPathMap depPathIdMap IntMap. ! fid
311+ ]
277312 pure TransitiveDependencies {.. }
278- where (g, fromVertex, toVertex) = graphFromEdges (map (\ (f, fs) -> (f, f, IntSet. toList fs)) $ IntMap. toList depModuleDeps)
279- vs = topSort g
313+ where
314+ (g, fromVertex, toVertex) = graphFromEdges (map (\ (f, fs) -> (f, f, IntSet. toList fs)) $ IntMap. toList depModuleDeps)
315+ vs = topSort g
280316
281317data TransitiveDependencies = TransitiveDependencies
282318 { transitiveModuleDeps :: [NormalizedFilePath ]
319+ , transitiveNamedModuleDeps :: [NamedModuleDep ]
283320 -- ^ Transitive module dependencies in topological order.
284321 -- The module itself is not included.
285322 , transitivePkgDeps :: [InstalledUnitId ]
286323 -- ^ Transitive pkg dependencies in unspecified order.
287324 } deriving (Eq , Show , Generic )
288325
289326instance NFData TransitiveDependencies
327+
328+ data NamedModuleDep = NamedModuleDep {
329+ nmdFilePath :: ! NormalizedFilePath ,
330+ nmdModuleName :: ! ModuleName ,
331+ nmdModLocation :: ! ModLocation
332+ }
333+ deriving Generic
334+
335+ instance Eq NamedModuleDep where
336+ a == b = nmdFilePath a == nmdFilePath b
337+
338+ instance NFData NamedModuleDep where
339+ rnf NamedModuleDep {.. } =
340+ rnf nmdFilePath `seq`
341+ rnf nmdModuleName `seq`
342+ -- 'ModLocation' lacks an 'NFData' instance
343+ rwhnf nmdModLocation
344+
345+ instance Show NamedModuleDep where
346+ show NamedModuleDep {.. } = show nmdFilePath
347+
0 commit comments