Cabal-1.23.1.0: A framework for packaging Haskell software

CopyrightIsaac Jones 2003-2004
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Distribution.Package

Contents

Description

Defines a package identifier along with a parser and pretty printer for it. PackageIdentifiers consist of a name and an exact version. It also defines a Dependency data type. A dependency is a package name and a version range, like "foo >= 1.2 && < 2".

Synopsis

Package ids

newtype PackageName Source

Constructors

PackageName 

Instances

Eq PackageName 
Data PackageName 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageName -> c PackageName Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageName Source

toConstr :: PackageName -> Constr Source

dataTypeOf :: PackageName -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c PackageName) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageName) Source

gmapT :: (forall b. Data b => b -> b) -> PackageName -> PackageName Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageName -> r Source

gmapQ :: (forall d. Data d => d -> u) -> PackageName -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageName -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageName -> m PackageName Source

Ord PackageName 
Read PackageName 
Show PackageName 
Generic PackageName 

Associated Types

type Rep PackageName :: * -> * Source

Binary PackageName 
NFData PackageName 

Methods

rnf :: PackageName -> () Source

Text PackageName 
type Rep PackageName = D1 (MetaData "PackageName" "Distribution.Package" "Cabal-1.23.1.0" True) (C1 (MetaCons "PackageName" PrefixI True) (S1 (MetaSel (Just Symbol "unPackageName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) 

data PackageIdentifier Source

The name and version of a package.

Constructors

PackageIdentifier 

Fields

Instances

Eq PackageIdentifier 
Data PackageIdentifier 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageIdentifier -> c PackageIdentifier Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageIdentifier Source

toConstr :: PackageIdentifier -> Constr Source

dataTypeOf :: PackageIdentifier -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c PackageIdentifier) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageIdentifier) Source

gmapT :: (forall b. Data b => b -> b) -> PackageIdentifier -> PackageIdentifier Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageIdentifier -> r Source

gmapQ :: (forall d. Data d => d -> u) -> PackageIdentifier -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageIdentifier -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageIdentifier -> m PackageIdentifier Source

Ord PackageIdentifier 
Read PackageIdentifier 
Show PackageIdentifier 
Generic PackageIdentifier 
Binary PackageIdentifier 
NFData PackageIdentifier 

Methods

rnf :: PackageIdentifier -> () Source

Text PackageIdentifier 
Package PackageIdentifier 
type Rep PackageIdentifier = D1 (MetaData "PackageIdentifier" "Distribution.Package" "Cabal-1.23.1.0" False) (C1 (MetaCons "PackageIdentifier" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pkgName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PackageName)) (S1 (MetaSel (Just Symbol "pkgVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)))) 

type PackageId = PackageIdentifier Source

Type alias so we can use the shorter name PackageId.

Package keys/installed package IDs (used for linker symbols)

data ComponentId Source

A ComponentId uniquely identifies the transitive source code closure of a component. For non-Backpack components, it also serves as the basis for install paths, symbols, etc.

Constructors

ComponentId String 

Instances

Eq ComponentId 
Data ComponentId 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ComponentId -> c ComponentId Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ComponentId Source

toConstr :: ComponentId -> Constr Source

dataTypeOf :: ComponentId -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c ComponentId) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ComponentId) Source

gmapT :: (forall b. Data b => b -> b) -> ComponentId -> ComponentId Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ComponentId -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ComponentId -> r Source

gmapQ :: (forall d. Data d => d -> u) -> ComponentId -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> ComponentId -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ComponentId -> m ComponentId Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ComponentId -> m ComponentId Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ComponentId -> m ComponentId Source

Ord ComponentId 
Read ComponentId 
Show ComponentId 
Generic ComponentId 

Associated Types

type Rep ComponentId :: * -> * Source

Binary ComponentId 
NFData ComponentId 

Methods

rnf :: ComponentId -> () Source

Text ComponentId 
type Rep ComponentId = D1 (MetaData "ComponentId" "Distribution.Package" "Cabal-1.23.1.0" False) (C1 (MetaCons "ComponentId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) 

newtype UnitId Source

For now, there is no distinction between component IDs and unit IDs in Cabal.

Instances

Eq UnitId 

Methods

(==) :: UnitId -> UnitId -> Bool

(/=) :: UnitId -> UnitId -> Bool

Data UnitId 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnitId -> c UnitId Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnitId Source

toConstr :: UnitId -> Constr Source

dataTypeOf :: UnitId -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c UnitId) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnitId) Source

gmapT :: (forall b. Data b => b -> b) -> UnitId -> UnitId Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r Source

gmapQ :: (forall d. Data d => d -> u) -> UnitId -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnitId -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId Source

Ord UnitId 
Read UnitId 
Show UnitId 
Generic UnitId 

Associated Types

type Rep UnitId :: * -> * Source

Binary UnitId 
NFData UnitId 

Methods

rnf :: UnitId -> () Source

Text UnitId 
type Rep UnitId = D1 (MetaData "UnitId" "Distribution.Package" "Cabal-1.23.1.0" True) (C1 (MetaCons "SimpleUnitId" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ComponentId))) 

mkUnitId :: String -> UnitId Source

Makes a simple-style UnitId from a string.

mkLegacyUnitId :: PackageId -> UnitId Source

Make an old-style UnitId from a package identifier

getHSLibraryName :: UnitId -> String Source

Returns library name prefixed with HS, suitable for filenames

type InstalledPackageId = UnitId Source

Deprecated: Use UnitId instead

ABI hash

Package source dependencies

data Dependency Source

Describes a dependency on a source package (API)

Instances

Eq Dependency 
Data Dependency 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dependency -> c Dependency Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dependency Source

toConstr :: Dependency -> Constr Source

dataTypeOf :: Dependency -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Dependency) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dependency) Source

gmapT :: (forall b. Data b => b -> b) -> Dependency -> Dependency Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dependency -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dependency -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Dependency -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dependency -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dependency -> m Dependency Source

Read Dependency 
Show Dependency 
Generic Dependency 

Associated Types

type Rep Dependency :: * -> * Source

Binary Dependency 
Text Dependency 
type Rep Dependency = D1 (MetaData "Dependency" "Distribution.Package" "Cabal-1.23.1.0" False) (C1 (MetaCons "Dependency" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PackageName)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VersionRange)))) 

Package classes

class Package pkg where Source

Class of things that have a PackageIdentifier

Types in this class are all notions of a package. This allows us to have different types for the different phases that packages go though, from simple name/id, package description, configured or installed packages.

Not all kinds of packages can be uniquely identified by a PackageIdentifier. In particular, installed packages cannot, there may be many installed instances of the same source package.

Minimal complete definition

packageId

class Package pkg => HasUnitId pkg where Source

Packages that have an installed package ID

Minimal complete definition

installedUnitId

Methods

installedUnitId :: pkg -> UnitId Source

installedPackageId :: HasUnitId pkg => pkg -> UnitId Source

Deprecated: Use installedUnitId instead

Compatibility wrapper for pre-Cabal 1.23.

class HasUnitId pkg => PackageInstalled pkg where Source

Class of installed packages.

The primary data type which is an instance of this package is InstalledPackageInfo, but when we are doing install plans in Cabal install we may have other, installed package-like things which contain more metadata. Installed packages have exact dependencies installedDepends.

Minimal complete definition

installedDepends

Methods

installedDepends :: pkg -> [UnitId] Source