Cabal-3.6.0.0: A framework for packaging Haskell software
Copyright(c) The University of Glasgow 2004
Maintainerlibraries@haskell.org
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.InstalledPackageInfo

Description

This is the information about an installed package that is communicated to the ghc-pkg program in order to register a package. ghc-pkg now consumes this package format (as of version 6.4). This is specific to GHC at the moment.

The .cabal file format is for describing a package that is not yet installed. It has a lot of flexibility, like conditionals and dependency ranges. As such, that format is not at all suitable for describing a package that has already been built and installed. By the time we get to that stage, we have resolved all conditionals and resolved dependency version constraints to exact versions of dependent packages. So, this module defines the InstalledPackageInfo data structure that contains all the info we keep about an installed package. There is a parser and pretty printer. The textual format is rather simpler than the .cabal format: there are no sections, for example.

Synopsis

Documentation

data InstalledPackageInfo Source #

Instances

Instances details
IsNode InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Associated Types

type Key InstalledPackageInfo Source #

HasMungedPackageId InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

HasUnitId InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Package InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

PackageInstalled InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Structured InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Generic InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Associated Types

type Rep InstalledPackageInfo :: Type -> Type Source #

Read InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Show InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Binary InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

NFData InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Eq InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

Monoid (PackageIndex InstalledPackageInfo) Source # 
Instance details

Defined in Distribution.Simple.PackageIndex

Semigroup (PackageIndex InstalledPackageInfo) Source # 
Instance details

Defined in Distribution.Simple.PackageIndex

type Key InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

type Rep InstalledPackageInfo Source # 
Instance details

Defined in Distribution.Types.InstalledPackageInfo

type Rep InstalledPackageInfo = D1 ('MetaData "InstalledPackageInfo" "Distribution.Types.InstalledPackageInfo" "Cabal-3.6.0.0" 'False) (C1 ('MetaCons "InstalledPackageInfo" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "sourcePackageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PackageId) :*: S1 ('MetaSel ('Just "sourceLibName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibraryName)) :*: (S1 ('MetaSel ('Just "installedComponentId_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComponentId) :*: (S1 ('MetaSel ('Just "libVisibility") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LibraryVisibility) :*: S1 ('MetaSel ('Just "installedUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId)))) :*: ((S1 ('MetaSel ('Just "instantiatedWith") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ModuleName, OpenModule)]) :*: S1 ('MetaSel ('Just "compatPackageKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "license") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either License License)) :*: (S1 ('MetaSel ('Just "copyright") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "maintainer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText))))) :*: (((S1 ('MetaSel ('Just "author") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "stability") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText)) :*: (S1 ('MetaSel ('Just "homepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: (S1 ('MetaSel ('Just "pkgUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "synopsis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText)))) :*: ((S1 ('MetaSel ('Just "description") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: (S1 ('MetaSel ('Just "category") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortText) :*: S1 ('MetaSel ('Just "abiHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AbiHash))) :*: (S1 ('MetaSel ('Just "indefinite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "exposed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "exposedModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExposedModule])))))) :*: ((((S1 ('MetaSel ('Just "hiddenModules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModuleName]) :*: S1 ('MetaSel ('Just "trusted") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "importDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "libraryDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "libraryDynDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath])))) :*: ((S1 ('MetaSel ('Just "dataDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "hsLibraries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])) :*: (S1 ('MetaSel ('Just "extraLibraries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "extraGHCiLibraries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "includeDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]))))) :*: (((S1 ('MetaSel ('Just "includes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "depends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [UnitId])) :*: (S1 ('MetaSel ('Just "abiDepends") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [AbiDependency]) :*: (S1 ('MetaSel ('Just "ccOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "cxxOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))) :*: ((S1 ('MetaSel ('Just "ldOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: (S1 ('MetaSel ('Just "frameworkDirs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "frameworks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) :*: (S1 ('MetaSel ('Just "haddockInterfaces") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "haddockHTMLs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: S1 ('MetaSel ('Just "pkgRoot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)))))))))

installedOpenUnitId :: InstalledPackageInfo -> OpenUnitId Source #

Get the indefinite unit identity representing this package. This IS NOT guaranteed to give you a substitution; for instantiated packages you will get DefiniteUnitId (installedUnitId ipi). For indefinite libraries, however, you will correctly get an OpenUnitId with the appropriate OpenModuleSubst.

requiredSignatures :: InstalledPackageInfo -> Set ModuleName Source #

Returns the set of module names which need to be filled for an indefinite package, or the empty set if the package is definite.

data ExposedModule Source #

Instances

Instances details
Parsec ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

Pretty ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

Structured ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

Generic ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

Associated Types

type Rep ExposedModule :: Type -> Type Source #

Read ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

Show ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

Binary ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

NFData ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

Methods

rnf :: ExposedModule -> () Source #

Eq ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

type Rep ExposedModule Source # 
Instance details

Defined in Distribution.Types.ExposedModule

type Rep ExposedModule = D1 ('MetaData "ExposedModule" "Distribution.Types.ExposedModule" "Cabal-3.6.0.0" 'False) (C1 ('MetaCons "ExposedModule" 'PrefixI 'True) (S1 ('MetaSel ('Just "exposedName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModuleName) :*: S1 ('MetaSel ('Just "exposedReexport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe OpenModule))))

data AbiDependency Source #

An ABI dependency is a dependency on a library which also records the ABI hash (abiHash) of the library it depends on.

The primary utility of this is to enable an extra sanity when GHC loads libraries: it can check if the dependency has a matching ABI and if not, refuse to load this library. This information is critical if we are shadowing libraries; differences in the ABI hash let us know what packages get shadowed by the new version of a package.

Constructors

AbiDependency 

Instances

Instances details
Parsec AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

Pretty AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

Structured AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

Generic AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

Associated Types

type Rep AbiDependency :: Type -> Type Source #

Read AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

Show AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

Binary AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

NFData AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

Methods

rnf :: AbiDependency -> () Source #

Eq AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

type Rep AbiDependency Source # 
Instance details

Defined in Distribution.Types.AbiDependency

type Rep AbiDependency = D1 ('MetaData "AbiDependency" "Distribution.Types.AbiDependency" "Cabal-3.6.0.0" 'False) (C1 ('MetaCons "AbiDependency" 'PrefixI 'True) (S1 ('MetaSel ('Just "depUnitId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnitId) :*: S1 ('MetaSel ('Just "depAbiHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AbiHash)))

parseInstalledPackageInfo :: ByteString -> Either (NonEmpty String) ([String], InstalledPackageInfo) Source #

Return either errors, or IPI with list of warnings

showInstalledPackageInfo :: InstalledPackageInfo -> String Source #

Pretty print InstalledPackageInfo.

pkgRoot isn't printed, as ghc-pkg prints it manually (as GHC-8.4).

showFullInstalledPackageInfo :: InstalledPackageInfo -> String Source #

The variant of showInstalledPackageInfo which outputs pkgroot field too.

showInstalledPackageInfoField :: String -> Maybe (InstalledPackageInfo -> String) Source #

>>> let ipi = emptyInstalledPackageInfo { maintainer = "Tester" }
>>> fmap ($ ipi) $ showInstalledPackageInfoField "maintainer"
Just "maintainer: Tester"