hackport-0.7.2.1: Hackage and Portage integration tool
Copyright(c) David Himmelstrup 2005
Bjorn Bringert 2007
Duncan Coutts 2008
Maintainer[email protected]
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Solver.Types.PackageIndex

Description

An index of packages.

Synopsis

Package index data type

data PackageIndex pkg Source #

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

It can be searched efficiently by package name and version.

Instances

Instances details
Functor PackageIndex Source # 
Instance details

Defined in Distribution.Solver.Types.PackageIndex

Methods

fmap :: (a -> b) -> PackageIndex a -> PackageIndex b #

(<$) :: a -> PackageIndex b -> PackageIndex a #

Eq pkg => Eq (PackageIndex pkg) Source # 
Instance details

Defined in Distribution.Solver.Types.PackageIndex

Methods

(==) :: PackageIndex pkg -> PackageIndex pkg -> Bool #

(/=) :: PackageIndex pkg -> PackageIndex pkg -> Bool #

Read pkg => Read (PackageIndex pkg) Source # 
Instance details

Defined in Distribution.Solver.Types.PackageIndex

Show pkg => Show (PackageIndex pkg) Source # 
Instance details

Defined in Distribution.Solver.Types.PackageIndex

Generic (PackageIndex pkg) Source # 
Instance details

Defined in Distribution.Solver.Types.PackageIndex

Associated Types

type Rep (PackageIndex pkg) :: Type -> Type #

Methods

from :: PackageIndex pkg -> Rep (PackageIndex pkg) x #

to :: Rep (PackageIndex pkg) x -> PackageIndex pkg #

Package pkg => Semigroup (PackageIndex pkg) Source # 
Instance details

Defined in Distribution.Solver.Types.PackageIndex

Methods

(<>) :: PackageIndex pkg -> PackageIndex pkg -> PackageIndex pkg #

sconcat :: NonEmpty (PackageIndex pkg) -> PackageIndex pkg #

stimes :: Integral b => b -> PackageIndex pkg -> PackageIndex pkg #

Package pkg => Monoid (PackageIndex pkg) Source # 
Instance details

Defined in Distribution.Solver.Types.PackageIndex

Binary pkg => Binary (PackageIndex pkg) Source # 
Instance details

Defined in Distribution.Solver.Types.PackageIndex

Methods

put :: PackageIndex pkg -> Put #

get :: Get (PackageIndex pkg) #

putList :: [PackageIndex pkg] -> Put #

type Rep (PackageIndex pkg) Source # 
Instance details

Defined in Distribution.Solver.Types.PackageIndex

type Rep (PackageIndex pkg) = D1 ('MetaData "PackageIndex" "Distribution.Solver.Types.PackageIndex" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'True) (C1 ('MetaCons "PackageIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PackageName [pkg]))))

Creating an index

fromList :: Package pkg => [pkg] -> PackageIndex pkg Source #

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 pkg Source #

Merge two indexes.

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

override :: Package pkg => PackageIndex pkg -> PackageIndex pkg -> PackageIndex pkg Source #

Override-merge oftwo indexes.

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

insert :: Package pkg => pkg -> PackageIndex pkg -> PackageIndex pkg Source #

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 pkg Source #

Removes all packages with this (case-sensitive) name from the index.

deletePackageId :: Package pkg => PackageIdentifier -> PackageIndex pkg -> PackageIndex pkg Source #

Removes a single package from the index.

deleteDependency :: Package pkg => PackageName -> VersionRange -> PackageIndex pkg -> PackageIndex pkg Source #

Removes all packages satisfying this dependency from the index.

Queries

Precise lookups

elemByPackageId :: Package pkg => PackageIndex pkg -> PackageIdentifier -> Bool Source #

elemByPackageName :: Package pkg => PackageIndex pkg -> PackageName -> Bool Source #

lookupPackageName :: Package pkg => PackageIndex pkg -> PackageName -> [pkg] Source #

Does a case-sensitive search by package name.

lookupPackageId :: Package pkg => PackageIndex pkg -> PackageIdentifier -> Maybe pkg Source #

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 -> PackageName -> VersionRange -> [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 :: PackageIndex pkg -> String -> [(PackageName, [pkg])] 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 pkg -> String -> [(PackageName, [pkg])] Source #

Does a case-insensitive substring search by package name.

That is, all packages that contain the given string in their name.

searchWithPredicate :: PackageIndex pkg -> (String -> Bool) -> [(PackageName, [pkg])] Source #

Bulk queries

allPackages :: PackageIndex pkg -> [pkg] Source #

Get all the packages from the index.

allPackagesByName :: PackageIndex pkg -> [[pkg]] Source #

Get all the packages from the index.

They are grouped by package name, case-sensitively.