| Copyright | (c) David Himmelstrup 2005 Bjorn Bringert 2007 Duncan Coutts 2008-2009 | 
|---|---|
| Maintainer | cabal-devel@haskell.org | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Distribution.Simple.PackageIndex
Description
An index of packages whose primary key is UnitId.  Public libraries
 are additionally indexed by PackageName and Version.
 Technically, these are an index of *units* (so we should eventually
 rename it to UnitIndex); but in the absence of internal libraries
 or Backpack each unit is equivalent to a package.
While PackageIndex is parametric over what it actually records,
 it is in fact only ever instantiated with a single element:
 The InstalledPackageIndex (defined here) contains a graph of
 InstalledPackageInfos representing the packages in a
 package database stack.  It is used in a variety of ways:
- The primary use to let Cabal access the same installed
     package database which is used by GHC during compilation.
     For example, this data structure is used by 'ghc-pkg'
     and Cabalto do consistency checks on the database (are the references closed).
- Given a set of dependencies, we can compute the transitive closure of dependencies. This is to check if the versions of packages are consistent, and also needed by multiple tools (Haddock must be explicitly told about the every transitive package to do cross-package linking; preprocessors must know about the include paths of all transitive dependencies.)
This PackageIndex is NOT to be confused with
 PackageIndex, which indexes packages only by
 PackageName (this makes it suitable for indexing source packages,
 for which we don't know UnitIds.)
Synopsis
- type InstalledPackageIndex = PackageIndex InstalledPackageInfo
- data PackageIndex a
- fromList :: [InstalledPackageInfo] -> InstalledPackageIndex
- merge :: InstalledPackageIndex -> InstalledPackageIndex -> InstalledPackageIndex
- insert :: InstalledPackageInfo -> InstalledPackageIndex -> InstalledPackageIndex
- deleteUnitId :: UnitId -> InstalledPackageIndex -> InstalledPackageIndex
- deleteSourcePackageId :: PackageId -> InstalledPackageIndex -> InstalledPackageIndex
- deletePackageName :: PackageName -> InstalledPackageIndex -> InstalledPackageIndex
- lookupUnitId :: PackageIndex a -> UnitId -> Maybe a
- lookupComponentId :: PackageIndex a -> ComponentId -> Maybe a
- lookupSourcePackageId :: PackageIndex a -> PackageId -> [a]
- lookupPackageId :: PackageIndex a -> PackageId -> Maybe a
- lookupPackageName :: PackageIndex a -> PackageName -> [(Version, [a])]
- lookupDependency :: InstalledPackageIndex -> PackageName -> VersionRange -> [(Version, [InstalledPackageInfo])]
- lookupInternalDependency :: InstalledPackageIndex -> PackageName -> VersionRange -> LibraryName -> [(Version, [InstalledPackageInfo])]
- searchByName :: PackageIndex a -> String -> SearchResult [a]
- data SearchResult a- = None
- | Unambiguous a
- | Ambiguous [a]
 
- searchByNameSubstring :: PackageIndex a -> String -> [a]
- searchWithPredicate :: PackageIndex a -> (String -> Bool) -> [a]
- allPackages :: PackageIndex a -> [a]
- allPackagesByName :: PackageIndex a -> [(PackageName, [a])]
- allPackagesBySourcePackageId :: HasUnitId a => PackageIndex a -> [(PackageId, [a])]
- allPackagesBySourcePackageIdAndLibName :: HasUnitId a => PackageIndex a -> [((PackageId, LibraryName), [a])]
- brokenPackages :: PackageInstalled a => PackageIndex a -> [(a, [UnitId])]
- dependencyClosure :: InstalledPackageIndex -> [UnitId] -> Either InstalledPackageIndex [(InstalledPackageInfo, [UnitId])]
- reverseDependencyClosure :: PackageInstalled a => PackageIndex a -> [UnitId] -> [a]
- topologicalOrder :: PackageInstalled a => PackageIndex a -> [a]
- reverseTopologicalOrder :: PackageInstalled a => PackageIndex a -> [a]
- dependencyInconsistencies :: InstalledPackageIndex -> [(DepUniqueKey, [(UnitId, [InstalledPackageInfo])])]
- dependencyCycles :: PackageInstalled a => PackageIndex a -> [[a]]
- dependencyGraph :: PackageInstalled a => PackageIndex a -> (Graph, Vertex -> a, UnitId -> Maybe Vertex)
- moduleNameIndex :: InstalledPackageIndex -> Map ModuleName [InstalledPackageInfo]
Package index data type
type InstalledPackageIndex = PackageIndex InstalledPackageInfo Source #
The default package index which contains InstalledPackageInfo.  Normally
 use this.
data PackageIndex a Source #
The collection of information about packages from one or more PackageDBs.
 These packages generally should have an instance of PackageInstalled
Packages are uniquely identified in by their UnitId, they can
 also be efficiently looked up by package name or by name and version.
Instances
Creating an index
fromList :: [InstalledPackageInfo] -> InstalledPackageIndex Source #
Build an index out of a bunch of packages.
If there are duplicates by UnitId then later ones mask earlier
 ones.
Updates
merge :: InstalledPackageIndex -> InstalledPackageIndex -> InstalledPackageIndex Source #
Merge two indexes.
Packages from the second mask packages from the first if they have the exact
 same UnitId.
For packages with the same source PackageId, packages from the second are
 "preferred" over those from the first. Being preferred means they are top
 result when we do a lookup by source PackageId. This is the mechanism we
 use to prefer user packages over global packages.
deleteUnitId :: UnitId -> InstalledPackageIndex -> InstalledPackageIndex Source #
Removes a single installed package from the index.
deleteSourcePackageId :: PackageId -> InstalledPackageIndex -> InstalledPackageIndex Source #
Removes all packages with this source PackageId from the index.
deletePackageName :: PackageName -> InstalledPackageIndex -> InstalledPackageIndex Source #
Removes all packages with this (case-sensitive) name from the index.
NB: Does NOT delete internal libraries from this package.
Queries
Precise lookups
lookupUnitId :: PackageIndex a -> UnitId -> Maybe a Source #
Does a lookup by unit identifier.
Since multiple package DBs mask each other by UnitId,
 then we get back at most one package.
lookupComponentId :: PackageIndex a -> ComponentId -> Maybe a Source #
Does a lookup by component identifier.  In the absence
 of Backpack, this is just a lookupUnitId.
lookupSourcePackageId :: PackageIndex a -> PackageId -> [a] Source #
lookupPackageId :: PackageIndex a -> PackageId -> Maybe a Source #
Convenient alias of lookupSourcePackageId, but assuming only
 one package per package ID.
lookupPackageName :: PackageIndex a -> PackageName -> [(Version, [a])] Source #
Does a lookup by source package name.
lookupDependency :: InstalledPackageIndex -> PackageName -> VersionRange -> [(Version, [InstalledPackageInfo])] Source #
Does a lookup by source package name and a range of versions.
We get back any number of versions of the specified package name, all satisfying the version range constraint.
This does NOT work for internal dependencies, DO NOT use this
 function on those; use lookupInternalDependency instead.
INVARIANT: List of eligible InstalledPackageInfo is non-empty.
lookupInternalDependency :: InstalledPackageIndex -> PackageName -> VersionRange -> LibraryName -> [(Version, [InstalledPackageInfo])] Source #
Does a lookup by source package name and a range of versions.
We get back any number of versions of the specified package name, all satisfying the version range constraint.
INVARIANT: List of eligible InstalledPackageInfo is non-empty.
Case-insensitive searches
searchByName :: PackageIndex a -> String -> SearchResult [a] Source #
Does a case-insensitive search by package name.
If there is only one package that compares case-insensitively to this name then the search is unambiguous and we get back all versions of that package. If several match case-insensitively but one matches exactly then it is also unambiguous.
If however several match case-insensitively and none match exactly then we have an ambiguous result, and we get back all the versions of all the packages. The list of ambiguous results is split by exact package name. So it is a non-empty list of non-empty lists.
data SearchResult a Source #
Constructors
| None | |
| Unambiguous a | |
| Ambiguous [a] | 
searchByNameSubstring :: PackageIndex a -> String -> [a] Source #
Does a case-insensitive substring search by package name.
That is, all packages that contain the given string in their name.
searchWithPredicate :: PackageIndex a -> (String -> Bool) -> [a] Source #
Since: 3.4.0.0
Bulk queries
allPackages :: PackageIndex a -> [a] Source #
Get all the packages from the index.
allPackagesByName :: PackageIndex a -> [(PackageName, [a])] Source #
Get all the packages from the index.
They are grouped by package name (case-sensitively).
(Doesn't include private libraries.)
allPackagesBySourcePackageId :: HasUnitId a => PackageIndex a -> [(PackageId, [a])] Source #
Get all the packages from the index.
They are grouped by source package id (package name and version).
(Doesn't include private libraries)
allPackagesBySourcePackageIdAndLibName :: HasUnitId a => PackageIndex a -> [((PackageId, LibraryName), [a])] Source #
Get all the packages from the index.
They are grouped by source package id and library name.
This DOES include internal libraries.
Special queries
brokenPackages :: PackageInstalled a => PackageIndex a -> [(a, [UnitId])] Source #
All packages that have immediate dependencies that are not in the index.
Returns such packages along with the dependencies that they're missing.
dependencyClosure :: InstalledPackageIndex -> [UnitId] -> Either InstalledPackageIndex [(InstalledPackageInfo, [UnitId])] Source #
Tries to take the transitive closure of the package dependencies.
If the transitive closure is complete then it returns that subset of the
 index. Otherwise it returns the broken packages as in brokenPackages.
- Note that if the result is Right []it is because at least one of the original givenPackageIds do not occur in the index.
reverseDependencyClosure :: PackageInstalled a => PackageIndex a -> [UnitId] -> [a] Source #
Takes the transitive closure of the packages reverse dependencies.
- The given PackageIds must be in the index.
topologicalOrder :: PackageInstalled a => PackageIndex a -> [a] Source #
reverseTopologicalOrder :: PackageInstalled a => PackageIndex a -> [a] Source #
dependencyInconsistencies :: InstalledPackageIndex -> [(DepUniqueKey, [(UnitId, [InstalledPackageInfo])])] Source #
Given a package index where we assume we want to use all the packages
 (use dependencyClosure if you need to get such a index subset) find out
 if the dependencies within it use consistent versions of each package.
 Return all cases where multiple packages depend on different versions of
 some other package.
Each element in the result is a package name along with the packages that depend on it and the versions they require. These are guaranteed to be distinct.
dependencyCycles :: PackageInstalled a => PackageIndex a -> [[a]] Source #
Find if there are any cycles in the dependency graph. If there are no
 cycles the result is [].
This actually computes the strongly connected components. So it gives us a list of groups of packages where within each group they all depend on each other, directly or indirectly.
dependencyGraph :: PackageInstalled a => PackageIndex a -> (Graph, Vertex -> a, UnitId -> Maybe Vertex) Source #
Builds a graph of the package dependencies.
Dependencies on other packages that are not in the index are discarded.
 You can check if there are any such dependencies with brokenPackages.
moduleNameIndex :: InstalledPackageIndex -> Map ModuleName [InstalledPackageInfo] Source #
A rough approximation of GHC's module finder, takes a
 InstalledPackageIndex and turns it into a map from module names to their
 source packages.  It's used to initialize the build-deps field in cabal
 init.