Cabal-1.24.2.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 Source # 
Data PackageName Source # 

Methods

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

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

toConstr :: PackageName -> Constr #

dataTypeOf :: PackageName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PackageName Source # 
Read PackageName Source # 
Show PackageName Source # 
Generic PackageName Source # 

Associated Types

type Rep PackageName :: * -> * #

Binary PackageName Source # 
NFData PackageName Source # 

Methods

rnf :: PackageName -> () #

Text PackageName Source # 
type Rep PackageName Source # 
type Rep PackageName = D1 (MetaData "PackageName" "Distribution.Package" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" 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 Source # 
Data PackageIdentifier Source # 

Methods

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

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

toConstr :: PackageIdentifier -> Constr #

dataTypeOf :: PackageIdentifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PackageIdentifier Source # 
Read PackageIdentifier Source # 
Show PackageIdentifier Source # 
Generic PackageIdentifier Source # 
Binary PackageIdentifier Source # 
NFData PackageIdentifier Source # 

Methods

rnf :: PackageIdentifier -> () #

Text PackageIdentifier Source # 
Package PackageIdentifier Source # 
type Rep PackageIdentifier Source # 
type Rep PackageIdentifier = D1 (MetaData "PackageIdentifier" "Distribution.Package" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" 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 Source # 
Data ComponentId Source # 

Methods

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

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

toConstr :: ComponentId -> Constr #

dataTypeOf :: ComponentId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ComponentId Source # 
Read ComponentId Source # 
Show ComponentId Source # 
Generic ComponentId Source # 

Associated Types

type Rep ComponentId :: * -> * #

Binary ComponentId Source # 
NFData ComponentId Source # 

Methods

rnf :: ComponentId -> () #

Text ComponentId Source # 
type Rep ComponentId Source # 
type Rep ComponentId = D1 (MetaData "ComponentId" "Distribution.Package" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" 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 Source # 

Methods

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

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

Data UnitId Source # 

Methods

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

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

toConstr :: UnitId -> Constr #

dataTypeOf :: UnitId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UnitId Source # 
Read UnitId Source # 
Show UnitId Source # 
Generic UnitId Source # 

Associated Types

type Rep UnitId :: * -> * #

Methods

from :: UnitId -> Rep UnitId x #

to :: Rep UnitId x -> UnitId #

Binary UnitId Source # 

Methods

put :: UnitId -> Put #

get :: Get UnitId #

putList :: [UnitId] -> Put #

NFData UnitId Source # 

Methods

rnf :: UnitId -> () #

Text UnitId Source # 
type Rep UnitId Source # 
type Rep UnitId = D1 (MetaData "UnitId" "Distribution.Package" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" 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

newtype AbiHash Source #

Constructors

AbiHash String 

Instances

Package source dependencies

data Dependency Source #

Describes a dependency on a source package (API)

Instances

Eq Dependency Source # 
Data Dependency Source # 

Methods

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

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

toConstr :: Dependency -> Constr #

dataTypeOf :: Dependency -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Dependency Source # 
Show Dependency Source # 
Generic Dependency Source # 

Associated Types

type Rep Dependency :: * -> * #

Binary Dependency Source # 
Text Dependency Source # 
type Rep Dependency Source # 

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