Cabal-2.2.0.0: A framework for packaging Haskell software

Copyright(c) The University of Glasgow 2004
Maintainerlibraries@haskell.org
Portabilityportable
Safe HaskellNone
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
Eq InstalledPackageInfo Source # 
Instance details
Read InstalledPackageInfo Source # 
Instance details
Show InstalledPackageInfo Source # 
Instance details
Generic InstalledPackageInfo Source # 
Instance details

Associated Types

type Rep InstalledPackageInfo :: * -> * #

Binary InstalledPackageInfo Source # 
Instance details
NFData InstalledPackageInfo Source # 
Instance details

Methods

rnf :: InstalledPackageInfo -> () #

IsNode InstalledPackageInfo Source # 
Instance details

Associated Types

type Key InstalledPackageInfo :: * Source #

PackageInstalled InstalledPackageInfo Source # 
Instance details
HasUnitId InstalledPackageInfo Source # 
Instance details
HasMungedPackageId InstalledPackageInfo Source # 
Instance details
Package InstalledPackageInfo Source # 
Instance details
Semigroup (PackageIndex InstalledPackageInfo) # 
Instance details
Monoid (PackageIndex InstalledPackageInfo) # 
Instance details
type Rep InstalledPackageInfo Source # 
Instance details
type Rep InstalledPackageInfo = D1 (MetaData "InstalledPackageInfo" "Distribution.Types.InstalledPackageInfo" "Cabal-2.2.0.0-inplace" False) (C1 (MetaCons "InstalledPackageInfo" PrefixI True) (((((S1 (MetaSel (Just "sourcePackageId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PackageId) :*: S1 (MetaSel (Just "sourceLibName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe UnqualComponentName))) :*: (S1 (MetaSel (Just "installedComponentId_") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ComponentId) :*: (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 NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "maintainer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "author") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) :*: (((S1 (MetaSel (Just "stability") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "homepage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "pkgUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "synopsis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) :*: ((S1 (MetaSel (Just "category") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: 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 "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)))))))))
type Key InstalledPackageInfo Source # 
Instance details

installedPackageId :: InstalledPackageInfo -> UnitId Source #

Deprecated: Use installedUnitId instead

Backwards compatibility with Cabal pre-1.24.

This type synonym is slightly awful because in cabal-install we define an InstalledPackageId but it's a ComponentId, not a UnitId!

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
Eq ExposedModule Source # 
Instance details
Read ExposedModule Source # 
Instance details
Show ExposedModule Source # 
Instance details
Generic ExposedModule Source # 
Instance details

Associated Types

type Rep ExposedModule :: * -> * #

Binary ExposedModule Source # 
Instance details
NFData ExposedModule Source # 
Instance details

Methods

rnf :: ExposedModule -> () #

Pretty ExposedModule Source # 
Instance details
Parsec ExposedModule Source # 
Instance details
Text ExposedModule Source # 
Instance details
type Rep ExposedModule Source # 
Instance details
type Rep ExposedModule = D1 (MetaData "ExposedModule" "Distribution.Types.ExposedModule" "Cabal-2.2.0.0-inplace" 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
Eq AbiDependency Source # 
Instance details
Read AbiDependency Source # 
Instance details
Show AbiDependency Source # 
Instance details
Generic AbiDependency Source # 
Instance details

Associated Types

type Rep AbiDependency :: * -> * #

Binary AbiDependency Source # 
Instance details
NFData AbiDependency Source # 
Instance details

Methods

rnf :: AbiDependency -> () #

Pretty AbiDependency Source # 
Instance details
Parsec AbiDependency Source # 
Instance details
Text AbiDependency Source # 
Instance details
type Rep AbiDependency Source # 
Instance details
type Rep AbiDependency = D1 (MetaData "AbiDependency" "Distribution.Types.AbiDependency" "Cabal-2.2.0.0-inplace" False) (C1 (MetaCons "AbiDependency" PrefixI True) (S1 (MetaSel (Just "depUnitId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UnitId) :*: S1 (MetaSel (Just "depAbiHash") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AbiHash)))

data ParseResult a Source #

Constructors

ParseFailed PError 
ParseOk [PWarning] a 
Instances
Monad ParseResult Source # 
Instance details
Functor ParseResult Source # 
Instance details

Methods

fmap :: (a -> b) -> ParseResult a -> ParseResult b #

(<$) :: a -> ParseResult b -> ParseResult a #

MonadFail ParseResult Source # 
Instance details

Methods

fail :: String -> ParseResult a #

Applicative ParseResult Source # 
Instance details

Methods

pure :: a -> ParseResult a #

(<*>) :: ParseResult (a -> b) -> ParseResult a -> ParseResult b #

liftA2 :: (a -> b -> c) -> ParseResult a -> ParseResult b -> ParseResult c #

(*>) :: ParseResult a -> ParseResult b -> ParseResult b #

(<*) :: ParseResult a -> ParseResult b -> ParseResult a #

Show a => Show (ParseResult a) Source # 
Instance details

data PError Source #

Constructors

AmbiguousParse String LineNo 
NoParse String LineNo 
TabsError LineNo 
FromString String (Maybe LineNo) 
Instances
Eq PError Source # 
Instance details

Methods

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

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

Show PError Source # 
Instance details

data PWarning Source #

Instances
Eq PWarning Source # 
Instance details
Show PWarning Source # 
Instance details

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"