ghc-9.0.1: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Unit.Info

Description

Info about installed units (compiled libraries)

Synopsis

Documentation

data GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod Source #

Information about an unit (a unit is an installed module library).

This is a subset of Cabal's InstalledPackageInfo, with just the bits that GHC is interested in.

Some types are left as parameters to be instantiated differently in ghc-pkg and in ghc itself.

Constructors

GenericUnitInfo 

Fields

  • unitId :: uid

    Unique unit identifier that is used during compilation (e.g. to generate symbols).

  • unitInstanceOf :: compid

    Identifier of an indefinite unit (i.e. with module holes) that this unit is an instance of.

  • unitInstantiations :: [(modulename, mod)]

    How this unit instantiates some of its module holes. Map hole module names to actual module

  • unitPackageId :: srcpkgid

    Source package identifier.

    Cabal instantiates this with Distribution.Types.PackageId.PackageId type which only contains the source package name and version. Notice that it doesn't contain the Hackage revision, nor any kind of hash.

  • unitPackageName :: srcpkgname

    Source package name

  • unitPackageVersion :: Version

    Source package version

  • unitComponentName :: Maybe srcpkgname

    Name of the component.

    Cabal supports more than one components (libraries, executables, testsuites) in the same package. Each component has a name except the default one (that can only be a library component) for which we use Nothing.

    GHC only deals with "library" components as they are the only kind of components that can be registered in a database and used by other modules.

  • unitAbiHash :: String

    ABI hash used to avoid mixing up units compiled with different dependencies, compiler, options, etc.

  • unitDepends :: [uid]

    Identifiers of the units this one depends on

  • unitAbiDepends :: [(uid, String)]

    Like unitDepends, but each dependency is annotated with the ABI hash we expect the dependency to respect.

  • unitImportDirs :: [FilePath]

    Directories containing module interfaces

  • unitLibraries :: [String]

    Names of the Haskell libraries provided by this unit

  • unitExtDepLibsSys :: [String]

    Names of the external system libraries that this unit depends on. See also unitExtDepLibsGhc field.

  • unitExtDepLibsGhc :: [String]

    Because of slight differences between the GHC dynamic linker (in GHC.Runtime.Linker) and the native system linker, some packages have to link with a different list of libraries when using GHC's. Examples include: libs that are actually gnu ld scripts, and the possibility that the .a libs do not exactly match the .so/.dll equivalents.

    If this field is set, then we use that instead of the unitExtDepLibsSys field.

  • unitLibraryDirs :: [FilePath]

    Directories containing libraries provided by this unit. See also unitLibraryDynDirs.

    It seems to be used to store paths to external library dependencies too.

  • unitLibraryDynDirs :: [FilePath]

    Directories containing the dynamic libraries provided by this unit. See also unitLibraryDirs.

    It seems to be used to store paths to external dynamic library dependencies too.

  • unitExtDepFrameworks :: [String]

    Names of the external MacOS frameworks that this unit depends on.

  • unitExtDepFrameworkDirs :: [FilePath]

    Directories containing MacOS frameworks that this unit depends on.

  • unitLinkerOptions :: [String]

    Linker (e.g. ld) command line options

  • unitCcOptions :: [String]

    C compiler options that needs to be passed to the C compiler when we compile some C code against this unit.

  • unitIncludes :: [String]

    C header files that are required by this unit (provided by this unit or external)

  • unitIncludeDirs :: [FilePath]

    Directories containing C header files that this unit depends on.

  • unitHaddockInterfaces :: [FilePath]

    Paths to Haddock interface files for this unit

  • unitHaddockHTMLs :: [FilePath]

    Paths to Haddock directories containing HTML files

  • unitExposedModules :: [(modulename, Maybe mod)]

    Modules exposed by the unit.

    A module can be re-exported from another package. In this case, we indicate the module origin in the second parameter.

  • unitHiddenModules :: [modulename]

    Hidden modules.

    These are useful for error reporting (e.g. if a hidden module is imported)

  • unitIsIndefinite :: Bool

    True if this unit has some module holes that need to be instantiated with real modules to make the unit usable (a.k.a. Backpack).

  • unitIsExposed :: Bool

    True if the unit is exposed. A unit could be installed in a database by "disabled" by not being exposed.

  • unitIsTrusted :: Bool

    True if the unit is trusted (cf Safe Haskell)

Instances

Instances details
Binary DbUnitInfo 
Instance details

Defined in GHC.Unit.Database

(Eq uid, Eq compid, Eq modulename, Eq mod, Eq srcpkgid, Eq srcpkgname) => Eq (GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod) 
Instance details

Defined in GHC.Unit.Database

Methods

(==) :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> Bool #

(/=) :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> Bool #

(Show uid, Show compid, Show modulename, Show mod, Show srcpkgid, Show srcpkgname) => Show (GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod) 
Instance details

Defined in GHC.Unit.Database

Methods

showsPrec :: Int -> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> ShowS Source #

show :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> String Source #

showList :: [GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod] -> ShowS Source #

type GenUnitInfo unit = GenericUnitInfo (Indefinite unit) PackageId PackageName unit ModuleName (GenModule (GenUnit unit)) Source #

Information about an installed unit

We parameterize on the unit identifier: * UnitKey: identifier used in the database (cf UnitKeyInfo) * UnitId: identifier used to generate code (cf UnitInfo)

These two identifiers are different for wired-in packages. See Note [About Units] in GHC.Unit

type UnitInfo = GenUnitInfo UnitId Source #

Information about an installed unit (units are identified by their internal UnitId)

newtype UnitKey Source #

A unit key in the database

Constructors

UnitKey FastString 

type UnitKeyInfo = GenUnitInfo UnitKey Source #

Information about an installed unit (units are identified by their database UnitKey)

mkUnitKeyInfo :: DbUnitInfo -> UnitKeyInfo Source #

Convert a DbUnitInfo (read from a package database) into UnitKeyInfo

mapUnitInfo :: (u -> v) -> (v -> FastString) -> GenUnitInfo u -> GenUnitInfo v Source #

Map over the unit parameter

mkUnitPprInfo :: GenUnitInfo u -> UnitPprInfo Source #

Create a UnitPprInfo from a UnitInfo

mkUnit :: UnitInfo -> Unit Source #

Make a Unit from a UnitInfo

If the unit is definite, make a RealUnit from unitId field.

If the unit is indefinite, make a VirtUnit from unitInstanceOf and unitInstantiations fields. Note that in this case we don't keep track of unitId. It can be retrieved later with "improvement", i.e. matching on `unitInstanceOf/unitInstantiations` fields (see Note [About units] in GHC.Unit).

newtype PackageId Source #

Constructors

PackageId FastString 

Instances

Instances details
Eq PackageId # 
Instance details

Defined in GHC.Unit.Info

Ord PackageId # 
Instance details

Defined in GHC.Unit.Info

Outputable PackageId # 
Instance details

Defined in GHC.Unit.Info

Uniquable PackageId # 
Instance details

Defined in GHC.Unit.Info

data Version Source #

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

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

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

toConstr :: Version -> Constr Source #

dataTypeOf :: Version -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Binary Version

Since: binary-0.8.0.0

Instance details

Defined in Data.Binary.Class

NFData Version

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Version -> () Source #

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