ghc-8.10.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

PackageConfig

Description

Package configuration information: essentially the interface to Cabal, with some utilities

(c) The University of Glasgow, 2004

Synopsis

Documentation

Mostly the compiler deals in terms of UnitIds, which are md5 hashes of a package ID, keys of its dependencies, and Cabal flags. You're expected to pass in the unit id in the -this-unit-id flag. However, for wired-in packages like base & rts, we don't necessarily know what the version is, so these are handled specially; see .

UnitId

The PackageConfig type: information about a package

data InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod #

This is a subset of Cabal's InstalledPackageInfo, with just the bits that GHC is interested in. See Cabal's documentation for a more detailed description of all of the fields.

Constructors

InstalledPackageInfo 

Fields

Instances

Instances details
(Eq instunitid, Eq compid, Eq modulename, Eq mod, Eq srcpkgid, Eq srcpkgname) => Eq (InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod) 
Instance details

Defined in GHC.PackageDb

Methods

(==) :: InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> Bool #

(/=) :: InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> Bool #

(Show instunitid, Show compid, Show modulename, Show mod, Show srcpkgid, Show srcpkgname) => Show (InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod) 
Instance details

Defined in GHC.PackageDb

Methods

showsPrec :: Int -> InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> ShowS #

show :: InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> String #

showList :: [InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod] -> ShowS #

RepInstalledPackageInfo a b c d e f g => Binary (InstalledPackageInfo a b c d e f g) 
Instance details

Defined in GHC.PackageDb

Methods

put :: InstalledPackageInfo a b c d e f g -> Put #

get :: Get (InstalledPackageInfo a b c d e f g) #

putList :: [InstalledPackageInfo a b c d e f g] -> Put #

newtype ComponentId Source #

A ComponentId consists of the package name, package version, component ID, the transitive dependencies of the component, and other information to uniquely identify the source code and build configuration of a component.

This used to be known as an InstalledPackageId, but a package can contain multiple components and a ComponentId uniquely identifies a component within a package. When a package only has one component, the ComponentId coincides with the InstalledPackageId

Constructors

ComponentId FastString 

Instances

Instances details
Eq ComponentId Source # 
Instance details

Defined in Module

Ord ComponentId Source # 
Instance details

Defined in Module

BinaryStringRep ComponentId Source # 
Instance details

Defined in Module

Outputable ComponentId Source # 
Instance details

Defined in Module

Uniquable ComponentId Source # 
Instance details

Defined in Module

Binary ComponentId Source # 
Instance details

Defined in Module

DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module Source # 
Instance details

Defined in Module

data Version #

A Version represents the version of a software entity.

An instance of Eq is provided, which implements exact equality modulo reordering of the tags in the versionTags field.

An instance of Ord is also provided, which gives lexicographic ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2, etc.). This is expected to be sufficient for many uses, but note that you may need to use a more specific ordering for your versioning scheme. For example, some versioning schemes may include pre-releases which have tags "pre1", "pre2", and so on, and these would need to be taken into account when determining ordering. In some cases, date ordering may be more appropriate, so the application would have to look for date tags in the versionTags field and compare those. The bottom line is, don't always assume that compare and other Ord operations are the right thing for every Version.

Similarly, concrete representations of versions may differ. One possible concrete representation is provided (see showVersion and parseVersion), but depending on the application a different concrete representation may be more appropriate.

Constructors

Version 

Fields

  • versionBranch :: [Int]

    The numeric branch for this version. This reflects the fact that most software versions are tree-structured; there is a main trunk which is tagged with versions at various points (1,2,3...), and the first branch off the trunk after version 3 is 3.1, the second branch off the trunk after version 3 is 3.2, and so on. The tree can be branched arbitrarily, just by adding more digits.

    We represent the branch as a list of Int, so version 3.2.1 becomes [3,2,1]. Lexicographic ordering (i.e. the default instance of Ord for [Int]) gives the natural ordering of branches.

  • versionTags :: [String]

    A version can be tagged with an arbitrary list of strings. The interpretation of the list of tags is entirely dependent on the entity that this version applies to.

Instances

Instances details
IsList Version

Since: base-4.8.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item Version #

Eq Version

Since: base-2.1

Instance details

Defined in Data.Version

Methods

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

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

Data Version

Since: base-4.7.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Version -> Constr #

dataTypeOf :: Version -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Version

Since: base-2.1

Instance details

Defined in Data.Version

Read Version

Since: base-2.1

Instance details

Defined in Data.Version

Show Version

Since: base-2.1

Instance details

Defined in Data.Version

Generic Version

Since: base-4.9.0.0

Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Binary Version

Since: binary-0.8.0.0

Instance details

Defined in Data.Binary.Class

Methods

put :: Version -> Put #

get :: Get Version #

putList :: [Version] -> Put #

NFData Version

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Version -> () #

type Rep Version 
Instance details

Defined in Data.Version

type Rep Version = D1 ('MetaData "Version" "Data.Version" "base" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "versionBranch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]) :*: S1 ('MetaSel ('Just "versionTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))
type Item Version 
Instance details

Defined in GHC.Exts