hackport-0.7.2.2: Hackage and Portage integration tool
CopyrightIsaac Jones 2003-2004
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Package

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

Documentation

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.0.2

Instances

Instances details
Eq AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

Methods

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

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

Read AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

Show AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

IsString AbiHash Source #

mkAbiHash

Since: 2.0.0.2

Instance details

Defined in Distribution.Types.AbiHash

Methods

fromString :: String -> AbiHash #

Generic AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

Associated Types

type Rep AbiHash :: Type -> Type #

Methods

from :: AbiHash -> Rep AbiHash x #

to :: Rep AbiHash x -> AbiHash #

Binary AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

Methods

put :: AbiHash -> Put #

get :: Get AbiHash #

putList :: [AbiHash] -> Put #

NFData AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

Methods

rnf :: AbiHash -> () #

Structured AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

Pretty AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

Parsec AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

type Rep AbiHash Source # 
Instance details

Defined in Distribution.Types.AbiHash

type Rep AbiHash = D1 ('MetaData "AbiHash" "Distribution.Types.AbiHash" "hackport-0.7.2.2-Jf8zaDrP5aANzq8F6jTnI-hackport-external-libs-Cabal" 'True) (C1 ('MetaCons "AbiHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))

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.0.2

mkAbiHash :: String -> AbiHash Source #

Convert AbiHash to String

Since: 2.0.0.2

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

Instances details
Eq Module Source # 
Instance details

Defined in Distribution.Types.Module

Methods

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

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

Data Module Source # 
Instance details

Defined in Distribution.Types.Module

Methods

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

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

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Module Source # 
Instance details

Defined in Distribution.Types.Module

Read Module Source # 
Instance details

Defined in Distribution.Types.Module

Show Module Source # 
Instance details

Defined in Distribution.Types.Module

Generic Module Source # 
Instance details

Defined in Distribution.Types.Module

Associated Types

type Rep Module :: Type -> Type #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Binary Module Source # 
Instance details

Defined in Distribution.Types.Module

Methods

put :: Module -> Put #

get :: Get Module #

putList :: [Module] -> Put #

NFData Module Source # 
Instance details

Defined in Distribution.Types.Module

Methods

rnf :: Module -> () #

Structured Module Source # 
Instance details

Defined in Distribution.Types.Module

Pretty Module Source # 
Instance details

Defined in Distribution.Types.Module

Parsec Module Source # 
Instance details

Defined in Distribution.Types.Module

Methods

parsec :: CabalParsing m => m Module Source #

type Rep Module Source # 
Instance details

Defined in Distribution.Types.Module

type Rep Module = D1 ('MetaData "Module" "Distribution.Types.Module" "hackport-0.7.2.2-Jf8zaDrP5aANzq8F6jTnI-hackport-external-libs-Cabal" 'False) (C1 ('MetaCons "Module" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DefUnitId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName)))

data PkgconfigName Source #

A pkg-config library name

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

Since: 2.0.0.2

Instances

Instances details
Eq PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

Data PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

Methods

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

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

toConstr :: PkgconfigName -> Constr #

dataTypeOf :: PkgconfigName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

Read PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

Show PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

IsString PkgconfigName Source #

mkPkgconfigName

Since: 2.0.0.2

Instance details

Defined in Distribution.Types.PkgconfigName

Generic PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

Associated Types

type Rep PkgconfigName :: Type -> Type #

Binary PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

NFData PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

Methods

rnf :: PkgconfigName -> () #

Structured PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

Pretty PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

Parsec PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

type Rep PkgconfigName Source # 
Instance details

Defined in Distribution.Types.PkgconfigName

type Rep PkgconfigName = D1 ('MetaData "PkgconfigName" "Distribution.Types.PkgconfigName" "hackport-0.7.2.2-Jf8zaDrP5aANzq8F6jTnI-hackport-external-libs-Cabal" 'True) (C1 ('MetaCons "PkgconfigName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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.0.2

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.

mungedName' :: HasMungedPackageId pkg => pkg -> MungedPackageName Source #

class Package pkg => HasUnitId pkg where Source #

Packages that have an installed unit ID

Methods

installedUnitId :: pkg -> UnitId Source #

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.

Methods

installedDepends :: pkg -> [UnitId] Source #