Copyright | (c) David Himmelstrup 2005, Bjorn Bringert 2007, Duncan Coutts 2008-2009 |
---|---|
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
An index of packages.
- type InstalledPackageIndex = PackageIndex InstalledPackageInfo
- data PackageIndex a
- fromList :: HasUnitId a => [a] -> PackageIndex a
- merge :: HasUnitId a => PackageIndex a -> PackageIndex a -> PackageIndex a
- insert :: HasUnitId a => a -> PackageIndex a -> PackageIndex a
- deleteUnitId :: HasUnitId a => UnitId -> PackageIndex a -> PackageIndex a
- deleteSourcePackageId :: HasUnitId a => PackageId -> PackageIndex a -> PackageIndex a
- deletePackageName :: HasUnitId a => PackageName -> PackageIndex a -> PackageIndex a
- lookupUnitId :: PackageIndex a -> UnitId -> Maybe a
- lookupSourcePackageId :: PackageIndex a -> PackageId -> [a]
- lookupPackageId :: PackageIndex a -> PackageId -> Maybe a
- lookupPackageName :: PackageIndex a -> PackageName -> [(Version, [a])]
- lookupDependency :: PackageIndex a -> Dependency -> [(Version, [a])]
- searchByName :: PackageIndex a -> String -> SearchResult [a]
- data SearchResult a
- = None
- | Unambiguous a
- | Ambiguous [a]
- searchByNameSubstring :: PackageIndex a -> String -> [a]
- allPackages :: PackageIndex a -> [a]
- allPackagesByName :: PackageIndex a -> [(PackageName, [a])]
- allPackagesBySourcePackageId :: HasUnitId a => PackageIndex a -> [(PackageId, [a])]
- brokenPackages :: PackageInstalled a => PackageIndex a -> [(a, [UnitId])]
- dependencyClosure :: PackageInstalled a => PackageIndex a -> [UnitId] -> Either (PackageIndex a) [(a, [UnitId])]
- reverseDependencyClosure :: PackageInstalled a => PackageIndex a -> [UnitId] -> [a]
- topologicalOrder :: PackageInstalled a => PackageIndex a -> [a]
- reverseTopologicalOrder :: PackageInstalled a => PackageIndex a -> [a]
- dependencyInconsistencies :: PackageInstalled a => PackageIndex a -> [(PackageName, [(PackageId, Version)])]
- dependencyCycles :: PackageInstalled a => PackageIndex a -> [[a]]
- dependencyGraph :: PackageInstalled a => PackageIndex a -> (Graph, Vertex -> a, UnitId -> Maybe Vertex)
- moduleNameIndex :: InstalledPackageIndex -> Map ModuleName [InstalledPackageInfo]
- deleteInstalledPackageId :: HasUnitId a => UnitId -> PackageIndex a -> PackageIndex a
- lookupInstalledPackageId :: PackageIndex a -> UnitId -> Maybe a
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 PackageDB
s.
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.
Eq a => Eq (PackageIndex a) | |
Read a => Read (PackageIndex a) | |
Show a => Show (PackageIndex a) | |
Generic (PackageIndex a) | |
HasUnitId a => Semigroup (PackageIndex a) | |
HasUnitId a => Monoid (PackageIndex a) | |
Binary a => Binary (PackageIndex a) | |
type Rep (PackageIndex a) = D1 (MetaData "PackageIndex" "Distribution.Simple.PackageIndex" "Cabal-1.23.1.0" False) (C1 (MetaCons "PackageIndex" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map UnitId a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Map PackageName (Map Version [a])))))) |
Creating an index
fromList :: HasUnitId a => [a] -> PackageIndex a Source
Build an index out of a bunch of packages.
If there are duplicates by UnitId
then later ones mask earlier
ones.
Updates
merge :: HasUnitId a => PackageIndex a -> PackageIndex a -> PackageIndex a 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.
insert :: HasUnitId a => a -> PackageIndex a -> PackageIndex a Source
deleteUnitId :: HasUnitId a => UnitId -> PackageIndex a -> PackageIndex a Source
Removes a single installed package from the index.
deleteSourcePackageId :: HasUnitId a => PackageId -> PackageIndex a -> PackageIndex a Source
Removes all packages with this source PackageId
from the index.
deletePackageName :: HasUnitId a => PackageName -> PackageIndex a -> PackageIndex a Source
Removes all packages with this (case-sensitive) name from the index.
Queries
Precise lookups
lookupUnitId :: PackageIndex a -> UnitId -> Maybe a Source
Does a lookup by source package id (name & version).
Since multiple package DBs mask each other by UnitId
,
then we get back at most one package.
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 :: PackageIndex a -> Dependency -> [(Version, [a])] 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.
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
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.
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).
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).
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 :: PackageInstalled a => PackageIndex a -> [UnitId] -> Either (PackageIndex a) [(a, [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 givenPackageId
s 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
PackageId
s must be in the index.
topologicalOrder :: PackageInstalled a => PackageIndex a -> [a] Source
reverseTopologicalOrder :: PackageInstalled a => PackageIndex a -> [a] Source
dependencyInconsistencies :: PackageInstalled a => PackageIndex a -> [(PackageName, [(PackageId, Version)])] 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
.
Backwards compatibility
deleteInstalledPackageId :: HasUnitId a => UnitId -> PackageIndex a -> PackageIndex a Source
Deprecated: Use deleteUnitId instead
Backwards compatibility wrapper for pre-Cabal 1.23.
lookupInstalledPackageId :: PackageIndex a -> UnitId -> Maybe a Source
Deprecated: Use lookupUnitId instead
Backwards compatibility for pre Cabal-1.23.