Cabal-2.0.0.0: A framework for packaging Haskell software

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

Distribution.Package (signature[?])

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

data PackageName Source #

A package name.

Use mkPackageName and unPackageName to convert from/to a String.

This type is opaque since Cabal-2.0

Since: 2.0

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 (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PackageName) Source #

dataCast2 :: Typeable (* -> * -> *) 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 # 
IsString PackageName #

mkPackageName

Since: 2.0

Generic PackageName # 

Associated Types

type Rep PackageName :: * -> * Source #

NFData PackageName # 

Methods

rnf :: PackageName -> () Source #

Binary PackageName # 
Text PackageName # 
type Rep PackageName # 
type Rep PackageName = D1 * (MetaData "PackageName" "Distribution.Package" "Cabal-2.0.0.0" True) (C1 * (MetaCons "PackageName" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ShortText)))

mkPackageName :: String -> PackageName Source #

Construct a PackageName from a String

mkPackageName is the inverse to unPackageName

Note: No validations are performed to ensure that the resulting PackageName is valid

Since: 2.0

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 (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PackageIdentifier) Source #

dataCast2 :: Typeable (* -> * -> *) 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 # 
NFData PackageIdentifier # 

Methods

rnf :: PackageIdentifier -> () Source #

Binary PackageIdentifier # 
Text PackageIdentifier # 
Package PackageIdentifier # 
type Rep PackageIdentifier # 
type Rep PackageIdentifier = D1 * (MetaData "PackageIdentifier" "Distribution.Package" "Cabal-2.0.0.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.

data PkgconfigName Source #

A pkg-config library name

This is parsed as any valid argument to the pkg-config utility.

Since: 2.0

Instances

Eq PkgconfigName # 
Data PkgconfigName # 

Methods

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

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

toConstr :: PkgconfigName -> Constr Source #

dataTypeOf :: PkgconfigName -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PkgconfigName) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PkgconfigName) Source #

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

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

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

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

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

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

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

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

Ord PkgconfigName # 
Read PkgconfigName # 
Show PkgconfigName # 
IsString PkgconfigName #

mkPkgconfigName

Since: 2.0

Generic PkgconfigName # 
NFData PkgconfigName # 

Methods

rnf :: PkgconfigName -> () Source #

Binary PkgconfigName # 
Text PkgconfigName # 
type Rep PkgconfigName # 
type Rep PkgconfigName = D1 * (MetaData "PkgconfigName" "Distribution.Package" "Cabal-2.0.0.0" True) (C1 * (MetaCons "PkgconfigName" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ShortText)))

mkPkgconfigName :: String -> PkgconfigName Source #

Construct a PkgconfigName from a String

mkPkgconfigName is the inverse to unPkgconfigName

Note: No validations are performed to ensure that the resulting PkgconfigName is valid

Since: 2.0

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

data ComponentId Source #

A ComponentId uniquely identifies the transitive source code closure of a component (i.e. libraries, executables).

For non-Backpack components, this corresponds one to one with the UnitId, which serves as the basis for install paths, linker symbols, etc.

Use mkComponentId and unComponentId to convert from/to a String.

This type is opaque since Cabal-2.0

Since: 2.0

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 (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ComponentId) Source #

dataCast2 :: Typeable (* -> * -> *) 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 # 
IsString ComponentId #

mkComponentId

Since: 2.0

Generic ComponentId # 

Associated Types

type Rep ComponentId :: * -> * Source #

NFData ComponentId # 

Methods

rnf :: ComponentId -> () Source #

Binary ComponentId # 
Text ComponentId # 
type Rep ComponentId # 
type Rep ComponentId = D1 * (MetaData "ComponentId" "Distribution.Package" "Cabal-2.0.0.0" True) (C1 * (MetaCons "ComponentId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ShortText)))

mkComponentId :: String -> ComponentId Source #

Construct a ComponentId from a String

mkComponentId is the inverse to unComponentId

Note: No validations are performed to ensure that the resulting ComponentId is valid

Since: 2.0

data UnitId Source #

A unit identifier identifies a (possibly instantiated) package/component that can be installed the installed package database. There are several types of components that can be installed:

  • A traditional library with no holes, so that unitIdHash is Nothing. In the absence of Backpack, UnitId is the same as a ComponentId.
  • An indefinite, Backpack library with holes. In this case, unitIdHash is still Nothing, but in the install, there are only interfaces, no compiled objects.
  • An instantiated Backpack library with all the holes filled in. unitIdHash is a Just a hash of the instantiating mapping.

A unit is a component plus the additional information on how the holes are filled in. Thus there is a one to many relationship: for a particular component there are many different ways of filling in the holes, and each different combination is a unit (and has a separate UnitId).

UnitId is distinct from OpenUnitId, in that it is always installed, whereas OpenUnitId are intermediate unit identities that arise during mixin linking, and don't necessarily correspond to any actually installed unit. Since the mapping is not actually recorded in a UnitId, you can't actually substitute over them (but you can substitute over OpenUnitId). See also Distribution.Backpack.FullUnitId for a mechanism for expanding an instantiated UnitId to retrieve its mapping.

Backwards compatibility note: if you need to get the string representation of a UnitId to pass, e.g., as a -package-id flag, use the display function, which will work on all versions of 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 (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UnitId) Source #

dataCast2 :: Typeable (* -> * -> *) 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 # 
IsString UnitId #

mkUnitId

Since: 2.0

Generic UnitId # 

Associated Types

type Rep UnitId :: * -> * Source #

NFData UnitId # 

Methods

rnf :: UnitId -> () Source #

Binary UnitId # 
Text UnitId #

The textual format for UnitId coincides with the format GHC accepts for -package-id.

type Rep UnitId # 
type Rep UnitId = D1 * (MetaData "UnitId" "Distribution.Package" "Cabal-2.0.0.0" True) (C1 * (MetaCons "UnitId" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ShortText)))

unUnitId :: UnitId -> String Source #

If you need backwards compatibility, consider using display instead, which is supported by all versions of Cabal.

data DefUnitId Source #

A UnitId for a definite package. The DefUnitId invariant says that a UnitId identified this way is definite; i.e., it has no unfilled holes.

Instances

Eq DefUnitId # 
Data DefUnitId # 

Methods

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

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

toConstr :: DefUnitId -> Constr Source #

dataTypeOf :: DefUnitId -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DefUnitId) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DefUnitId) Source #

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

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

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

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

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

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

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

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

Ord DefUnitId # 
Read DefUnitId # 
Show DefUnitId # 
Generic DefUnitId # 

Associated Types

type Rep DefUnitId :: * -> * Source #

NFData DefUnitId # 

Methods

rnf :: DefUnitId -> () Source #

Binary DefUnitId # 
Text DefUnitId # 
type Rep DefUnitId # 
type Rep DefUnitId = D1 * (MetaData "DefUnitId" "Distribution.Package" "Cabal-2.0.0.0" True) (C1 * (MetaCons "DefUnitId" PrefixI True) (S1 * (MetaSel (Just Symbol "unDefUnitId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * UnitId)))

unsafeMkDefUnitId :: UnitId -> DefUnitId Source #

Unsafely create a DefUnitId from a UnitId. Your responsibility is to ensure that the DefUnitId invariant holds.

newSimpleUnitId :: ComponentId -> UnitId Source #

Create a unit identity with no associated hash directly from a ComponentId.

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

Modules

data Module Source #

A module identity uniquely identifies a Haskell module by qualifying a ModuleName with the UnitId which defined it. This type distinguishes between two packages which provide a module with the same name, or a module from the same package compiled with different dependencies. There are a few cases where Cabal needs to know about module identities, e.g., when writing out reexported modules in the InstalledPackageInfo.

Instances

Eq Module # 

Methods

(==) :: Module -> Module -> Bool #

(/=) :: Module -> Module -> Bool #

Data Module # 

Methods

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

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

toConstr :: Module -> Constr Source #

dataTypeOf :: Module -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Module) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) Source #

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

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

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

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

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

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

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

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

Ord Module # 
Read Module # 
Show Module # 
Generic Module # 

Associated Types

type Rep Module :: * -> * Source #

NFData Module # 

Methods

rnf :: Module -> () Source #

Binary Module # 
Text Module # 
type Rep Module # 

ABI hash

data AbiHash Source #

ABI Hashes

Use mkAbiHash and unAbiHash to convert from/to a String.

This type is opaque since Cabal-2.0

Since: 2.0

unAbiHash :: AbiHash -> String Source #

Construct a AbiHash from a String

mkAbiHash is the inverse to unAbiHash

Note: No validations are performed to ensure that the resulting AbiHash is valid

Since: 2.0

mkAbiHash :: String -> AbiHash Source #

Convert AbiHash to String

Since: 2.0

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 unit ID

Minimal complete definition

installedUnitId

Methods

installedUnitId :: pkg -> UnitId Source #

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

Deprecated: Use installedUnitId instead

Compatibility wrapper for Cabal pre-1.24.

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 #