1 | {-# LANGUAGE DeriveGeneric #-} |
2 | {-# LANGUAGE FlexibleContexts #-} |
3 | {-# LANGUAGE FlexibleInstances #-} |
4 | |
5 | ----------------------------------------------------------------------------- |
6 | |
7 | -- | |
8 | -- Module : Distribution.Simple.PackageIndex |
9 | -- Copyright : (c) David Himmelstrup 2005, |
10 | -- Bjorn Bringert 2007, |
11 | -- Duncan Coutts 2008-2009 |
12 | -- |
13 | -- Maintainer : cabal-devel@haskell.org |
14 | -- Portability : portable |
15 | -- |
16 | -- An index of packages whose primary key is 'UnitId'. Public libraries |
17 | -- are additionally indexed by 'PackageName' and 'Version'. |
18 | -- Technically, these are an index of *units* (so we should eventually |
19 | -- rename it to 'UnitIndex'); but in the absence of internal libraries |
20 | -- or Backpack each unit is equivalent to a package. |
21 | -- |
22 | -- While 'PackageIndex' is parametric over what it actually records, |
23 | -- it is in fact only ever instantiated with a single element: |
24 | -- The 'InstalledPackageIndex' (defined here) contains a graph of |
25 | -- 'InstalledPackageInfo's representing the packages in a |
26 | -- package database stack. It is used in a variety of ways: |
27 | -- |
28 | -- * The primary use to let Cabal access the same installed |
29 | -- package database which is used by GHC during compilation. |
30 | -- For example, this data structure is used by 'ghc-pkg' |
31 | -- and 'Cabal' to do consistency checks on the database |
32 | -- (are the references closed). |
33 | -- |
34 | -- * Given a set of dependencies, we can compute the transitive |
35 | -- closure of dependencies. This is to check if the versions |
36 | -- of packages are consistent, and also needed by multiple |
37 | -- tools (Haddock must be explicitly told about the every |
38 | -- transitive package to do cross-package linking; |
39 | -- preprocessors must know about the include paths of all |
40 | -- transitive dependencies.) |
41 | -- |
42 | -- This 'PackageIndex' is NOT to be confused with |
43 | -- 'Distribution.Client.PackageIndex', which indexes packages only by |
44 | -- 'PackageName' (this makes it suitable for indexing source packages, |
45 | -- for which we don't know 'UnitId's.) |
46 | module Distribution.Simple.PackageIndex |
47 | ( -- * Package index data type |
48 | InstalledPackageIndex |
49 | , PackageIndex |
50 | |
51 | -- * Creating an index |
52 | , fromList |
53 | |
54 | -- * Updates |
55 | , merge |
56 | , insert |
57 | , deleteUnitId |
58 | , deleteSourcePackageId |
59 | , deletePackageName |
60 | -- deleteDependency, |
61 | |
62 | -- * Queries |
63 | |
64 | -- ** Precise lookups |
65 | , lookupUnitId |
66 | , lookupComponentId |
67 | , lookupSourcePackageId |
68 | , lookupPackageId |
69 | , lookupPackageName |
70 | , lookupDependency |
71 | , lookupInternalDependency |
72 | |
73 | -- ** Case-insensitive searches |
74 | , searchByName |
75 | , SearchResult (..) |
76 | , searchByNameSubstring |
77 | , searchWithPredicate |
78 | |
79 | -- ** Bulk queries |
80 | , allPackages |
81 | , allPackagesByName |
82 | , allPackagesBySourcePackageId |
83 | , allPackagesBySourcePackageIdAndLibName |
84 | |
85 | -- ** Special queries |
86 | , brokenPackages |
87 | , dependencyClosure |
88 | , reverseDependencyClosure |
89 | , topologicalOrder |
90 | , reverseTopologicalOrder |
91 | , dependencyInconsistencies |
92 | , dependencyCycles |
93 | , dependencyGraph |
94 | , moduleNameIndex |
95 | ) where |
96 | |
97 | import qualified Data.Map.Strict as Map |
98 | import Distribution.Compat.Prelude hiding (lookup) |
99 | import Prelude () |
100 | |
101 | import Distribution.Backpack |
102 | import qualified Distribution.InstalledPackageInfo as IPI |
103 | import Distribution.ModuleName |
104 | import Distribution.Package |
105 | import Distribution.Simple.Utils |
106 | import Distribution.Types.LibraryName |
107 | import Distribution.Version |
108 | |
109 | import Control.Exception (assert) |
110 | import Control.Monad |
111 | import Data.Array ((!)) |
112 | import qualified Data.Array as Array |
113 | import qualified Data.Graph as Graph |
114 | import Data.List as List (deleteBy, deleteFirstsBy, groupBy) |
115 | import qualified Data.List.NonEmpty as NE |
116 | import qualified Data.Tree as Tree |
117 | import Distribution.Compat.Stack |
118 | |
119 | import qualified Prelude (foldr1) |
120 | |
121 | -- | The collection of information about packages from one or more 'PackageDB's. |
122 | -- These packages generally should have an instance of 'PackageInstalled' |
123 | -- |
124 | -- Packages are uniquely identified in by their 'UnitId', they can |
125 | -- also be efficiently looked up by package name or by name and version. |
126 | data PackageIndex a = PackageIndex |
127 | { -- The primary index. Each InstalledPackageInfo record is uniquely identified |
128 | -- by its UnitId. |
129 | -- |
130 | unitIdIndex :: !(Map UnitId a) |
131 | , -- This auxiliary index maps package names (case-sensitively) to all the |
132 | -- versions and instances of that package. This allows us to find all |
133 | -- versions satisfying a dependency. |
134 | -- |
135 | -- It is a three-level index. The first level is the package name, |
136 | -- the second is the package version and the final level is instances |
137 | -- of the same package version. These are unique by UnitId |
138 | -- and are kept in preference order. |
139 | -- |
140 | -- FIXME: Clarify what "preference order" means. Check that this invariant is |
141 | -- preserved. See #1463 for discussion. |
142 | packageIdIndex :: !(Map (PackageName, LibraryName) (Map Version [a])) |
143 | } |
144 | deriving (Eq, Generic, Show, Read) |
145 | |
146 | instance Binary a => Binary (PackageIndex a) |
147 | instance Structured a => Structured (PackageIndex a) |
148 | |
149 | -- | The default package index which contains 'InstalledPackageInfo'. Normally |
150 | -- use this. |
151 | type InstalledPackageIndex = PackageIndex IPI.InstalledPackageInfo |
152 | |
153 | instance Monoid (PackageIndex IPI.InstalledPackageInfo) where |
154 | mempty = PackageIndex Map.empty Map.empty |
155 | mappend = (<>) |
156 | |
157 | -- save one mappend with empty in the common case: |
158 | mconcat [] = mempty |
159 | mconcat xs = Prelude.foldr1 mappend xs |
160 | |
161 | instance Semigroup (PackageIndex IPI.InstalledPackageInfo) where |
162 | (<>) = merge |
163 | |
164 | {-# NOINLINE invariant #-} |
165 | invariant :: WithCallStack (InstalledPackageIndex -> Bool) |
166 | invariant (PackageIndex pids pnames) = |
167 | -- trace (show pids' ++ "\n" ++ show pnames') $ |
168 | pids' == pnames' |
169 | where |
170 | pids' = map installedUnitId (Map.elems pids) |
171 | pnames' = |
172 | sort |
173 | [ assert pinstOk (installedUnitId pinst) |
174 | | ((pname, plib), pvers) <- Map.toList pnames |
175 | , let pversOk = not (Map.null pvers) |
176 | , (pver, pinsts) <- assert pversOk $ Map.toList pvers |
177 | , let pinsts' = sortBy (comparing installedUnitId) pinsts |
178 | pinstsOk = |
179 | all |
180 | (\g -> length g == 1) |
181 | (groupBy (equating installedUnitId) pinsts') |
182 | , pinst <- assert pinstsOk $ pinsts' |
183 | , let pinstOk = |
184 | packageName pinst == pname |
185 | && packageVersion pinst == pver |
186 | && IPI.sourceLibName pinst == plib |
187 | ] |
188 | |
189 | -- If you see this invariant failing (ie the assert in mkPackageIndex below) |
190 | -- then one thing to check is if it is happening in fromList. Check if the |
191 | -- second list above (the sort [...] bit) is ending up with duplicates. This |
192 | -- has been observed in practice once due to a messed up ghc-pkg db. How/why |
193 | -- it became messed up was not discovered. |
194 | |
195 | -- |
196 | |
197 | -- * Internal helpers |
198 | |
199 | -- |
200 | |
201 | mkPackageIndex |
202 | :: WithCallStack |
203 | ( Map UnitId IPI.InstalledPackageInfo |
204 | -> Map |
205 | (PackageName, LibraryName) |
206 | (Map Version [IPI.InstalledPackageInfo]) |
207 | -> InstalledPackageIndex |
208 | ) |
209 | mkPackageIndex pids pnames = assert (invariant index) index |
210 | where |
211 | index = PackageIndex pids pnames |
212 | |
213 | -- |
214 | |
215 | -- * Construction |
216 | |
217 | -- |
218 | |
219 | -- | Build an index out of a bunch of packages. |
220 | -- |
221 | -- If there are duplicates by 'UnitId' then later ones mask earlier |
222 | -- ones. |
223 | fromList :: [IPI.InstalledPackageInfo] -> InstalledPackageIndex |
224 | fromList pkgs = mkPackageIndex pids ((fmap . fmap) toList pnames) |
225 | where |
226 | pids = Map.fromList [(installedUnitId pkg, pkg) | pkg <- pkgs] |
227 | pnames = |
228 | Map.fromList |
229 | [ (liftM2 (,) packageName IPI.sourceLibName (NE.head pkgsN), pvers) |
230 | | pkgsN <- |
231 | NE.groupBy (equating (liftM2 (,) packageName IPI.sourceLibName)) |
232 | . sortBy (comparing (liftM3 (,,) packageName IPI.sourceLibName packageVersion)) |
233 | $ pkgs |
234 | , let pvers = |
235 | Map.fromList |
236 | [ ( packageVersion (NE.head pkgsNV) |
237 | , NE.nubBy (equating installedUnitId) (NE.reverse pkgsNV) |
238 | ) |
239 | | pkgsNV <- NE.groupBy (equating packageVersion) pkgsN |
240 | ] |
241 | ] |
242 | |
243 | -- |
244 | |
245 | -- * Updates |
246 | |
247 | -- |
248 | |
249 | -- | Merge two indexes. |
250 | -- |
251 | -- Packages from the second mask packages from the first if they have the exact |
252 | -- same 'UnitId'. |
253 | -- |
254 | -- For packages with the same source 'PackageId', packages from the second are |
255 | -- \"preferred\" over those from the first. Being preferred means they are top |
256 | -- result when we do a lookup by source 'PackageId'. This is the mechanism we |
257 | -- use to prefer user packages over global packages. |
258 | merge |
259 | :: InstalledPackageIndex |
260 | -> InstalledPackageIndex |
261 | -> InstalledPackageIndex |
262 | merge (PackageIndex pids1 pnames1) (PackageIndex pids2 pnames2) = |
263 | mkPackageIndex |
264 | (Map.unionWith (\_ y -> y) pids1 pids2) |
265 | (Map.unionWith (Map.unionWith mergeBuckets) pnames1 pnames2) |
266 | where |
267 | -- Packages in the second list mask those in the first, however preferred |
268 | -- packages go first in the list. |
269 | mergeBuckets xs ys = ys ++ (xs \\ ys) |
270 | (\\) = deleteFirstsBy (equating installedUnitId) |
271 | |
272 | -- | Inserts a single package into the index. |
273 | -- |
274 | -- This is equivalent to (but slightly quicker than) using 'mappend' or |
275 | -- 'merge' with a singleton index. |
276 | insert :: IPI.InstalledPackageInfo -> InstalledPackageIndex -> InstalledPackageIndex |
277 | insert pkg (PackageIndex pids pnames) = |
278 | mkPackageIndex pids' pnames' |
279 | where |
280 | pids' = Map.insert (installedUnitId pkg) pkg pids |
281 | pnames' = insertPackageName pnames |
282 | insertPackageName = |
283 | Map.insertWith |
284 | (\_ -> insertPackageVersion) |
285 | (packageName pkg, IPI.sourceLibName pkg) |
286 | (Map.singleton (packageVersion pkg) [pkg]) |
287 | |
288 | insertPackageVersion = |
289 | Map.insertWith |
290 | (\_ -> insertPackageInstance) |
291 | (packageVersion pkg) |
292 | [pkg] |
293 | |
294 | insertPackageInstance pkgs = |
295 | pkg : deleteBy (equating installedUnitId) pkg pkgs |
296 | |
297 | -- | Removes a single installed package from the index. |
298 | deleteUnitId |
299 | :: UnitId |
300 | -> InstalledPackageIndex |
301 | -> InstalledPackageIndex |
302 | deleteUnitId ipkgid original@(PackageIndex pids pnames) = |
303 | case Map.updateLookupWithKey (\_ _ -> Nothing) ipkgid pids of |
304 | (Nothing, _) -> original |
305 | (Just spkgid, pids') -> |
306 | mkPackageIndex |
307 | pids' |
308 | (deletePkgName spkgid pnames) |
309 | where |
310 | deletePkgName spkgid = |
311 | Map.update (deletePkgVersion spkgid) (packageName spkgid, IPI.sourceLibName spkgid) |
312 | |
313 | deletePkgVersion spkgid = |
314 | (\m -> if Map.null m then Nothing else Just m) |
315 | . Map.update deletePkgInstance (packageVersion spkgid) |
316 | |
317 | deletePkgInstance = |
318 | (\xs -> if null xs then Nothing else Just xs) |
319 | . List.deleteBy (\_ pkg -> installedUnitId pkg == ipkgid) undefined |
320 | |
321 | -- | Removes all packages with this source 'PackageId' from the index. |
322 | deleteSourcePackageId |
323 | :: PackageId |
324 | -> InstalledPackageIndex |
325 | -> InstalledPackageIndex |
326 | deleteSourcePackageId pkgid original@(PackageIndex pids pnames) = |
327 | -- NB: Doesn't delete internal packages |
328 | case Map.lookup (packageName pkgid, LMainLibName) pnames of |
329 | Nothing -> original |
330 | Just pvers -> case Map.lookup (packageVersion pkgid) pvers of |
331 | Nothing -> original |
332 | Just pkgs -> |
333 | mkPackageIndex |
334 | (foldl' (flip (Map.delete . installedUnitId)) pids pkgs) |
335 | (deletePkgName pnames) |
336 | where |
337 | deletePkgName = |
338 | Map.update deletePkgVersion (packageName pkgid, LMainLibName) |
339 | |
340 | deletePkgVersion = |
341 | (\m -> if Map.null m then Nothing else Just m) |
342 | . Map.delete (packageVersion pkgid) |
343 | |
344 | -- | Removes all packages with this (case-sensitive) name from the index. |
345 | -- |
346 | -- NB: Does NOT delete internal libraries from this package. |
347 | deletePackageName |
348 | :: PackageName |
349 | -> InstalledPackageIndex |
350 | -> InstalledPackageIndex |
351 | deletePackageName name original@(PackageIndex pids pnames) = |
352 | case Map.lookup (name, LMainLibName) pnames of |
353 | Nothing -> original |
354 | Just pvers -> |
355 | mkPackageIndex |
356 | ( foldl' |
357 | (flip (Map.delete . installedUnitId)) |
358 | pids |
359 | (concat (Map.elems pvers)) |
360 | ) |
361 | (Map.delete (name, LMainLibName) pnames) |
362 | |
363 | {- |
364 | -- | Removes all packages satisfying this dependency from the index. |
365 | -- |
366 | deleteDependency :: Dependency -> PackageIndex -> PackageIndex |
367 | deleteDependency (Dependency name verstionRange) = |
368 | delete' name (\pkg -> packageVersion pkg `withinRange` verstionRange) |
369 | -} |
370 | |
371 | -- |
372 | |
373 | -- * Bulk queries |
374 | |
375 | -- |
376 | |
377 | -- | Get all the packages from the index. |
378 | allPackages :: PackageIndex a -> [a] |
379 | allPackages = Map.elems . unitIdIndex |
380 | |
381 | -- | Get all the packages from the index. |
382 | -- |
383 | -- They are grouped by package name (case-sensitively). |
384 | -- |
385 | -- (Doesn't include private libraries.) |
386 | allPackagesByName :: PackageIndex a -> [(PackageName, [a])] |
387 | allPackagesByName index = |
388 | [ (pkgname, concat (Map.elems pvers)) |
389 | | ((pkgname, LMainLibName), pvers) <- Map.toList (packageIdIndex index) |
390 | ] |
391 | |
392 | -- | Get all the packages from the index. |
393 | -- |
394 | -- They are grouped by source package id (package name and version). |
395 | -- |
396 | -- (Doesn't include private libraries) |
397 | allPackagesBySourcePackageId |
398 | :: HasUnitId a |
399 | => PackageIndex a |
400 | -> [(PackageId, [a])] |
401 | allPackagesBySourcePackageId index = |
402 | [ (packageId ipkg, ipkgs) |
403 | | ((_, LMainLibName), pvers) <- Map.toList (packageIdIndex index) |
404 | , ipkgs@(ipkg : _) <- Map.elems pvers |
405 | ] |
406 | |
407 | -- | Get all the packages from the index. |
408 | -- |
409 | -- They are grouped by source package id and library name. |
410 | -- |
411 | -- This DOES include internal libraries. |
412 | allPackagesBySourcePackageIdAndLibName |
413 | :: HasUnitId a |
414 | => PackageIndex a |
415 | -> [((PackageId, LibraryName), [a])] |
416 | allPackagesBySourcePackageIdAndLibName index = |
417 | [ ((packageId ipkg, ln), ipkgs) |
418 | | ((_, ln), pvers) <- Map.toList (packageIdIndex index) |
419 | , ipkgs@(ipkg : _) <- Map.elems pvers |
420 | ] |
421 | |
422 | -- |
423 | |
424 | -- * Lookups |
425 | |
426 | -- |
427 | |
428 | -- | Does a lookup by unit identifier. |
429 | -- |
430 | -- Since multiple package DBs mask each other by 'UnitId', |
431 | -- then we get back at most one package. |
432 | lookupUnitId |
433 | :: PackageIndex a |
434 | -> UnitId |
435 | -> Maybe a |
436 | lookupUnitId index uid = Map.lookup uid (unitIdIndex index) |
437 | |
438 | -- | Does a lookup by component identifier. In the absence |
439 | -- of Backpack, this is just a 'lookupUnitId'. |
440 | lookupComponentId |
441 | :: PackageIndex a |
442 | -> ComponentId |
443 | -> Maybe a |
444 | lookupComponentId index cid = |
445 | Map.lookup (newSimpleUnitId cid) (unitIdIndex index) |
446 | |
447 | -- | Does a lookup by source package id (name & version). |
448 | -- |
449 | -- There can be multiple installed packages with the same source 'PackageId' |
450 | -- but different 'UnitId'. They are returned in order of |
451 | -- preference, with the most preferred first. |
452 | lookupSourcePackageId :: PackageIndex a -> PackageId -> [a] |
453 | lookupSourcePackageId index pkgid = |
454 | -- Do not lookup internal libraries |
455 | case Map.lookup (packageName pkgid, LMainLibName) (packageIdIndex index) of |
456 | Nothing -> [] |
457 | Just pvers -> case Map.lookup (packageVersion pkgid) pvers of |
458 | Nothing -> [] |
459 | Just pkgs -> pkgs -- in preference order |
460 | |
461 | -- | Convenient alias of 'lookupSourcePackageId', but assuming only |
462 | -- one package per package ID. |
463 | lookupPackageId :: PackageIndex a -> PackageId -> Maybe a |
464 | lookupPackageId index pkgid = case lookupSourcePackageId index pkgid of |
465 | [] -> Nothing |
466 | [pkg] -> Just pkg |
467 | _ -> error "Distribution.Simple.PackageIndex: multiple matches found" |
468 | |
469 | -- | Does a lookup by source package name. |
470 | lookupPackageName |
471 | :: PackageIndex a |
472 | -> PackageName |
473 | -> [(Version, [a])] |
474 | lookupPackageName index name = |
475 | -- Do not match internal libraries |
476 | case Map.lookup (name, LMainLibName) (packageIdIndex index) of |
477 | Nothing -> [] |
478 | Just pvers -> Map.toList pvers |
479 | |
480 | -- | Does a lookup by source package name and a range of versions. |
481 | -- |
482 | -- We get back any number of versions of the specified package name, all |
483 | -- satisfying the version range constraint. |
484 | -- |
485 | -- This does NOT work for internal dependencies, DO NOT use this |
486 | -- function on those; use 'lookupInternalDependency' instead. |
487 | -- |
488 | -- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty. |
489 | lookupDependency |
490 | :: InstalledPackageIndex |
491 | -> PackageName |
492 | -> VersionRange |
493 | -> [(Version, [IPI.InstalledPackageInfo])] |
494 | lookupDependency index pn vr = |
495 | -- Yes, a little bit of a misnomer here! |
496 | lookupInternalDependency index pn vr LMainLibName |
497 | |
498 | -- | Does a lookup by source package name and a range of versions. |
499 | -- |
500 | -- We get back any number of versions of the specified package name, all |
501 | -- satisfying the version range constraint. |
502 | -- |
503 | -- INVARIANT: List of eligible 'IPI.InstalledPackageInfo' is non-empty. |
504 | lookupInternalDependency |
505 | :: InstalledPackageIndex |
506 | -> PackageName |
507 | -> VersionRange |
508 | -> LibraryName |
509 | -> [(Version, [IPI.InstalledPackageInfo])] |
510 | lookupInternalDependency index name versionRange libn = |
511 | case Map.lookup (name, libn) (packageIdIndex index) of |
512 | Nothing -> [] |
513 | Just pvers -> |
514 | [ (ver, pkgs') |
515 | | (ver, pkgs) <- Map.toList pvers |
516 | , ver `withinRange` versionRange |
517 | , let pkgs' = filter eligible pkgs |
518 | , -- Enforce the invariant |
519 | not (null pkgs') |
520 | ] |
521 | where |
522 | -- When we select for dependencies, we ONLY want to pick up indefinite |
523 | -- packages, or packages with no instantiations. We'll do mix-in |
524 | -- linking to improve any such package into an instantiated one |
525 | -- later. |
526 | eligible pkg = IPI.indefinite pkg || null (IPI.instantiatedWith pkg) |
527 | |
528 | -- |
529 | |
530 | -- * Case insensitive name lookups |
531 | |
532 | -- |
533 | |
534 | -- | Does a case-insensitive search by package name. |
535 | -- |
536 | -- If there is only one package that compares case-insensitively to this name |
537 | -- then the search is unambiguous and we get back all versions of that package. |
538 | -- If several match case-insensitively but one matches exactly then it is also |
539 | -- unambiguous. |
540 | -- |
541 | -- If however several match case-insensitively and none match exactly then we |
542 | -- have an ambiguous result, and we get back all the versions of all the |
543 | -- packages. The list of ambiguous results is split by exact package name. So |
544 | -- it is a non-empty list of non-empty lists. |
545 | searchByName :: PackageIndex a -> String -> SearchResult [a] |
546 | searchByName index name = |
547 | -- Don't match internal packages |
548 | case [ pkgs | pkgs@((pname, LMainLibName), _) <- Map.toList (packageIdIndex index), lowercase (unPackageName pname) == lname |
549 | ] of |
550 | [] -> None |
551 | [(_, pvers)] -> Unambiguous (concat (Map.elems pvers)) |
552 | pkgss -> case find ((mkPackageName name ==) . fst . fst) pkgss of |
553 | Just (_, pvers) -> Unambiguous (concat (Map.elems pvers)) |
554 | Nothing -> Ambiguous (map (concat . Map.elems . snd) pkgss) |
555 | where |
556 | lname = lowercase name |
557 | |
558 | data SearchResult a = None | Unambiguous a | Ambiguous [a] |
559 | |
560 | -- | Does a case-insensitive substring search by package name. |
561 | -- |
562 | -- That is, all packages that contain the given string in their name. |
563 | searchByNameSubstring :: PackageIndex a -> String -> [a] |
564 | searchByNameSubstring index searchterm = |
565 | searchWithPredicate index (\n -> lsearchterm `isInfixOf` lowercase n) |
566 | where |
567 | lsearchterm = lowercase searchterm |
568 | |
569 | -- | @since 3.4.0.0 |
570 | searchWithPredicate :: PackageIndex a -> (String -> Bool) -> [a] |
571 | searchWithPredicate index predicate = |
572 | [ pkg |
573 | | -- Don't match internal packages |
574 | ((pname, LMainLibName), pvers) <- Map.toList (packageIdIndex index) |
575 | , predicate (unPackageName pname) |
576 | , pkgs <- Map.elems pvers |
577 | , pkg <- pkgs |
578 | ] |
579 | |
580 | -- |
581 | |
582 | -- * Special queries |
583 | |
584 | -- |
585 | |
586 | -- None of the stuff below depends on the internal representation of the index. |
587 | -- |
588 | |
589 | -- | Find if there are any cycles in the dependency graph. If there are no |
590 | -- cycles the result is @[]@. |
591 | -- |
592 | -- This actually computes the strongly connected components. So it gives us a |
593 | -- list of groups of packages where within each group they all depend on each |
594 | -- other, directly or indirectly. |
595 | dependencyCycles :: PackageInstalled a => PackageIndex a -> [[a]] |
596 | dependencyCycles index = |
597 | [vs | Graph.CyclicSCC vs <- Graph.stronglyConnComp adjacencyList] |
598 | where |
599 | adjacencyList = |
600 | [ (pkg, installedUnitId pkg, installedDepends pkg) |
601 | | pkg <- allPackages index |
602 | ] |
603 | |
604 | -- | All packages that have immediate dependencies that are not in the index. |
605 | -- |
606 | -- Returns such packages along with the dependencies that they're missing. |
607 | brokenPackages |
608 | :: PackageInstalled a |
609 | => PackageIndex a |
610 | -> [(a, [UnitId])] |
611 | brokenPackages index = |
612 | [ (pkg, missing) |
613 | | pkg <- allPackages index |
614 | , let missing = |
615 | [ pkg' | pkg' <- installedDepends pkg, isNothing (lookupUnitId index pkg') |
616 | ] |
617 | , not (null missing) |
618 | ] |
619 | |
620 | -- | Tries to take the transitive closure of the package dependencies. |
621 | -- |
622 | -- If the transitive closure is complete then it returns that subset of the |
623 | -- index. Otherwise it returns the broken packages as in 'brokenPackages'. |
624 | -- |
625 | -- * Note that if the result is @Right []@ it is because at least one of |
626 | -- the original given 'PackageId's do not occur in the index. |
627 | dependencyClosure |
628 | :: InstalledPackageIndex |
629 | -> [UnitId] |
630 | -> Either |
631 | (InstalledPackageIndex) |
632 | [(IPI.InstalledPackageInfo, [UnitId])] |
633 | dependencyClosure index pkgids0 = case closure mempty [] pkgids0 of |
634 | (completed, []) -> Left completed |
635 | (completed, _) -> Right (brokenPackages completed) |
636 | where |
637 | closure completed failed [] = (completed, failed) |
638 | closure completed failed (pkgid : pkgids) = case lookupUnitId index pkgid of |
639 | Nothing -> closure completed (pkgid : failed) pkgids |
640 | Just pkg -> case lookupUnitId completed (installedUnitId pkg) of |
641 | Just _ -> closure completed failed pkgids |
642 | Nothing -> closure completed' failed pkgids' |
643 | where |
644 | completed' = insert pkg completed |
645 | pkgids' = installedDepends pkg ++ pkgids |
646 | |
647 | -- | Takes the transitive closure of the packages reverse dependencies. |
648 | -- |
649 | -- * The given 'PackageId's must be in the index. |
650 | reverseDependencyClosure |
651 | :: PackageInstalled a |
652 | => PackageIndex a |
653 | -> [UnitId] |
654 | -> [a] |
655 | reverseDependencyClosure index = |
656 | map vertexToPkg |
657 | . concatMap Tree.flatten |
658 | . Graph.dfs reverseDepGraph |
659 | . map (fromMaybe noSuchPkgId . pkgIdToVertex) |
660 | where |
661 | (depGraph, vertexToPkg, pkgIdToVertex) = dependencyGraph index |
662 | reverseDepGraph = Graph.transposeG depGraph |
663 | noSuchPkgId = error "reverseDependencyClosure: package is not in the graph" |
664 | |
665 | topologicalOrder :: PackageInstalled a => PackageIndex a -> [a] |
666 | topologicalOrder index = |
667 | map toPkgId |
668 | . Graph.topSort |
669 | $ graph |
670 | where |
671 | (graph, toPkgId, _) = dependencyGraph index |
672 | |
673 | reverseTopologicalOrder :: PackageInstalled a => PackageIndex a -> [a] |
674 | reverseTopologicalOrder index = |
675 | map toPkgId |
676 | . Graph.topSort |
677 | . Graph.transposeG |
678 | $ graph |
679 | where |
680 | (graph, toPkgId, _) = dependencyGraph index |
681 | |
682 | -- | Builds a graph of the package dependencies. |
683 | -- |
684 | -- Dependencies on other packages that are not in the index are discarded. |
685 | -- You can check if there are any such dependencies with 'brokenPackages'. |
686 | dependencyGraph |
687 | :: PackageInstalled a |
688 | => PackageIndex a |
689 | -> ( Graph.Graph |
690 | , Graph.Vertex -> a |
691 | , UnitId -> Maybe Graph.Vertex |
692 | ) |
693 | dependencyGraph index = (graph, vertex_to_pkg, id_to_vertex) |
694 | where |
695 | graph = |
696 | Array.listArray |
697 | bounds |
698 | [ [v | Just v <- map id_to_vertex (installedDepends pkg)] |
699 | | pkg <- pkgs |
700 | ] |
701 | |
702 | pkgs = sortBy (comparing packageId) (allPackages index) |
703 | vertices = zip (map installedUnitId pkgs) [0 ..] |
704 | vertex_map = Map.fromList vertices |
705 | id_to_vertex pid = Map.lookup pid vertex_map |
706 | |
707 | vertex_to_pkg vertex = pkgTable ! vertex |
708 | |
709 | pkgTable = Array.listArray bounds pkgs |
710 | topBound = length pkgs - 1 |
711 | bounds = (0, topBound) |
712 | |
713 | -- | We maintain the invariant that, for any 'DepUniqueKey', there |
714 | -- is only one instance of the package in our database. |
715 | type DepUniqueKey = (PackageName, LibraryName, Map ModuleName OpenModule) |
716 | |
717 | -- | Given a package index where we assume we want to use all the packages |
718 | -- (use 'dependencyClosure' if you need to get such a index subset) find out |
719 | -- if the dependencies within it use consistent versions of each package. |
720 | -- Return all cases where multiple packages depend on different versions of |
721 | -- some other package. |
722 | -- |
723 | -- Each element in the result is a package name along with the packages that |
724 | -- depend on it and the versions they require. These are guaranteed to be |
725 | -- distinct. |
726 | dependencyInconsistencies |
727 | :: InstalledPackageIndex |
728 | -- At DepUniqueKey... |
729 | -> [ ( DepUniqueKey |
730 | , -- There were multiple packages (BAD!) |
731 | [ ( UnitId |
732 | , -- And here are the packages which |
733 | -- immediately depended on it |
734 | [IPI.InstalledPackageInfo] |
735 | ) |
736 | ] |
737 | ) |
738 | ] |
739 | dependencyInconsistencies index = do |
740 | (dep_key, insts_map) <- Map.toList inverseIndex |
741 | let insts = Map.toList insts_map |
742 | guard (length insts >= 2) |
743 | return (dep_key, insts) |
744 | where |
745 | inverseIndex :: Map DepUniqueKey (Map UnitId [IPI.InstalledPackageInfo]) |
746 | inverseIndex = Map.fromListWith (Map.unionWith (++)) $ do |
747 | pkg <- allPackages index |
748 | dep_ipid <- installedDepends pkg |
749 | Just dep <- [lookupUnitId index dep_ipid] |
750 | let dep_key = |
751 | ( packageName dep |
752 | , IPI.sourceLibName dep |
753 | , Map.fromList (IPI.instantiatedWith dep) |
754 | ) |
755 | return (dep_key, Map.singleton dep_ipid [pkg]) |
756 | |
757 | -- | A rough approximation of GHC's module finder, takes a |
758 | -- 'InstalledPackageIndex' and turns it into a map from module names to their |
759 | -- source packages. It's used to initialize the @build-deps@ field in @cabal |
760 | -- init@. |
761 | moduleNameIndex :: InstalledPackageIndex -> Map ModuleName [IPI.InstalledPackageInfo] |
762 | moduleNameIndex index = |
763 | Map.fromListWith (++) $ do |
764 | pkg <- allPackages index |
765 | IPI.ExposedModule m reexport <- IPI.exposedModules pkg |
766 | case reexport of |
767 | Nothing -> return (m, [pkg]) |
768 | Just (OpenModuleVar _) -> [] |
769 | Just (OpenModule _ m') |
770 | | m == m' -> [] |
771 | | otherwise -> return (m', [pkg]) |
772 | |
773 | -- The heuristic is this: we want to prefer the original package |
774 | -- which originally exported a module. However, if a reexport |
775 | -- also *renamed* the module (m /= m'), then we have to use the |
776 | -- downstream package, since the upstream package has the wrong |
777 | -- module name! |