Cabal-1.6.0.3: A framework for packaging Haskell softwareSource codeContentsIndex
Distribution.Simple.PackageIndex
Portabilityportable
Maintainercabal-devel@haskell.org
Contents
Package index data type
Creating an index
Updates
Queries
Precise lookups
Case-insensitive searches
Bulk queries
Special queries
Description
An index of packages.
Synopsis
data Package pkg => PackageIndex pkg
fromList :: Package pkg => [pkg] -> PackageIndex pkg
merge :: Package pkg => PackageIndex pkg -> PackageIndex pkg -> PackageIndex pkg
insert :: Package pkg => pkg -> PackageIndex pkg -> PackageIndex pkg
deletePackageName :: Package pkg => PackageName -> PackageIndex pkg -> PackageIndex pkg
deletePackageId :: Package pkg => PackageIdentifier -> PackageIndex pkg -> PackageIndex pkg
deleteDependency :: Package pkg => Dependency -> PackageIndex pkg -> PackageIndex pkg
lookupPackageName :: Package pkg => PackageIndex pkg -> PackageName -> [pkg]
lookupPackageId :: Package pkg => PackageIndex pkg -> PackageIdentifier -> Maybe pkg
lookupDependency :: Package pkg => PackageIndex pkg -> Dependency -> [pkg]
searchByName :: Package pkg => PackageIndex pkg -> String -> SearchResult [pkg]
data SearchResult a
= None
| Unambiguous a
| Ambiguous [a]
searchByNameSubstring :: Package pkg => PackageIndex pkg -> String -> [pkg]
allPackages :: Package pkg => PackageIndex pkg -> [pkg]
allPackagesByName :: Package pkg => PackageIndex pkg -> [[pkg]]
brokenPackages :: PackageFixedDeps pkg => PackageIndex pkg -> [(pkg, [PackageIdentifier])]
dependencyClosure :: PackageFixedDeps pkg => PackageIndex pkg -> [PackageIdentifier] -> Either (PackageIndex pkg) [(pkg, [PackageIdentifier])]
reverseDependencyClosure :: PackageFixedDeps pkg => PackageIndex pkg -> [PackageIdentifier] -> [pkg]
topologicalOrder :: PackageFixedDeps pkg => PackageIndex pkg -> [pkg]
reverseTopologicalOrder :: PackageFixedDeps pkg => PackageIndex pkg -> [pkg]
dependencyInconsistencies :: PackageFixedDeps pkg => PackageIndex pkg -> [(PackageName, [(PackageIdentifier, Version)])]
dependencyCycles :: PackageFixedDeps pkg => PackageIndex pkg -> [[pkg]]
dependencyGraph :: PackageFixedDeps pkg => PackageIndex pkg -> (Graph, Vertex -> pkg, PackageIdentifier -> Maybe Vertex)
Package index data type
data Package pkg => PackageIndex pkg Source

The collection of information about packages from one or more PackageDBs.

It can be searched effeciently by package name and version.

show/hide Instances
(Read pkg, Package pkg) => Read (PackageIndex pkg)
(Show pkg, Package pkg) => Show (PackageIndex pkg)
Package pkg => Monoid (PackageIndex pkg)
Creating an index
fromList :: Package pkg => [pkg] -> PackageIndex pkgSource

Build an index out of a bunch of packages.

If there are duplicates, later ones mask earlier ones.

Updates
merge :: Package pkg => PackageIndex pkg -> PackageIndex pkg -> PackageIndex pkgSource

Merge two indexes.

Packages from the second mask packages of the same exact name (case-sensitively) from the first.

insert :: Package pkg => pkg -> PackageIndex pkg -> PackageIndex pkgSource

Inserts a single package into the index.

This is equivalent to (but slightly quicker than) using mappend or merge with a singleton index.

deletePackageName :: Package pkg => PackageName -> PackageIndex pkg -> PackageIndex pkgSource
Removes all packages with this (case-sensitive) name from the index.
deletePackageId :: Package pkg => PackageIdentifier -> PackageIndex pkg -> PackageIndex pkgSource
Removes a single package from the index.
deleteDependency :: Package pkg => Dependency -> PackageIndex pkg -> PackageIndex pkgSource
Removes all packages satisfying this dependency from the index.
Queries
Precise lookups
lookupPackageName :: Package pkg => PackageIndex pkg -> PackageName -> [pkg]Source
Does a case-sensitive search by package name.
lookupPackageId :: Package pkg => PackageIndex pkg -> PackageIdentifier -> Maybe pkgSource

Does a lookup by package id (name & version).

Since multiple package DBs mask each other case-sensitively by package name, then we get back at most one package.

lookupDependency :: Package pkg => PackageIndex pkg -> Dependency -> [pkg]Source

Does a case-sensitive search by 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 :: Package pkg => PackageIndex pkg -> String -> SearchResult [pkg]Source

Does a case-insensitive search by package name.

If there is only one package that compares case-insentiviely to this name then the search is unambiguous and we get back all versions of that package. If several match case-insentiviely but one matches exactly then it is also unambiguous.

If however several match case-insentiviely 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 :: Package pkg => PackageIndex pkg -> String -> [pkg]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 :: Package pkg => PackageIndex pkg -> [pkg]Source
Get all the packages from the index.
allPackagesByName :: Package pkg => PackageIndex pkg -> [[pkg]]Source

Get all the packages from the index.

They are grouped by package name, case-sensitively.

Special queries
brokenPackages :: PackageFixedDeps pkg => PackageIndex pkg -> [(pkg, [PackageIdentifier])]Source

All packages that have dependencies that are not in the index.

Returns such packages along with the dependencies that they're missing.

dependencyClosure :: PackageFixedDeps pkg => PackageIndex pkg -> [PackageIdentifier] -> Either (PackageIndex pkg) [(pkg, [PackageIdentifier])]Source

Tries to take the transative closure of the package dependencies.

If the transative 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 given PackageIdentifiers do not occur in the index.
reverseDependencyClosure :: PackageFixedDeps pkg => PackageIndex pkg -> [PackageIdentifier] -> [pkg]Source

Takes the transative closure of the packages reverse dependencies.

topologicalOrder :: PackageFixedDeps pkg => PackageIndex pkg -> [pkg]Source
reverseTopologicalOrder :: PackageFixedDeps pkg => PackageIndex pkg -> [pkg]Source
dependencyInconsistencies :: PackageFixedDeps pkg => PackageIndex pkg -> [(PackageName, [(PackageIdentifier, 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 :: PackageFixedDeps pkg => PackageIndex pkg -> [[pkg]]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 :: PackageFixedDeps pkg => PackageIndex pkg -> (Graph, Vertex -> pkg, PackageIdentifier -> 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.

Produced by Haddock version 2.4.2