Copyright | (c) The University of Glasgow 2004 |
---|---|
Maintainer | libraries@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
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
- data InstalledPackageInfo = InstalledPackageInfo {
- sourcePackageId :: PackageId
- sourceLibName :: LibraryName
- installedComponentId_ :: ComponentId
- libVisibility :: LibraryVisibility
- installedUnitId :: UnitId
- instantiatedWith :: [(ModuleName, OpenModule)]
- compatPackageKey :: String
- license :: Either License License
- copyright :: !ShortText
- maintainer :: !ShortText
- author :: !ShortText
- stability :: !ShortText
- homepage :: !ShortText
- pkgUrl :: !ShortText
- synopsis :: !ShortText
- description :: !ShortText
- category :: !ShortText
- abiHash :: AbiHash
- indefinite :: Bool
- exposed :: Bool
- exposedModules :: [ExposedModule]
- hiddenModules :: [ModuleName]
- trusted :: Bool
- importDirs :: [FilePath]
- libraryDirs :: [FilePath]
- libraryDirsStatic :: [FilePath]
- libraryDynDirs :: [FilePath]
- dataDir :: FilePath
- hsLibraries :: [String]
- extraLibraries :: [String]
- extraLibrariesStatic :: [String]
- extraGHCiLibraries :: [String]
- includeDirs :: [FilePath]
- includes :: [String]
- depends :: [UnitId]
- abiDepends :: [AbiDependency]
- ccOptions :: [String]
- cxxOptions :: [String]
- ldOptions :: [String]
- frameworkDirs :: [FilePath]
- frameworks :: [String]
- haddockInterfaces :: [FilePath]
- haddockHTMLs :: [FilePath]
- pkgRoot :: Maybe FilePath
- installedComponentId :: InstalledPackageInfo -> ComponentId
- installedOpenUnitId :: InstalledPackageInfo -> OpenUnitId
- sourceComponentName :: InstalledPackageInfo -> ComponentName
- requiredSignatures :: InstalledPackageInfo -> Set ModuleName
- data ExposedModule = ExposedModule {}
- data AbiDependency = AbiDependency {
- depUnitId :: UnitId
- depAbiHash :: AbiHash
- emptyInstalledPackageInfo :: InstalledPackageInfo
- parseInstalledPackageInfo :: ByteString -> Either (NonEmpty String) ([String], InstalledPackageInfo)
- showInstalledPackageInfo :: InstalledPackageInfo -> String
- showFullInstalledPackageInfo :: InstalledPackageInfo -> String
- showInstalledPackageInfoField :: String -> Maybe (InstalledPackageInfo -> String)
- showSimpleInstalledPackageInfoField :: String -> Maybe (InstalledPackageInfo -> String)
Documentation
data InstalledPackageInfo Source #
Constructors
Instances
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 #
Constructors
ExposedModule | |
Fields |
Instances
Parsec ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule Methods parsec :: CabalParsing m => m ExposedModule Source # | |||||
Pretty ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule Methods pretty :: ExposedModule -> Doc Source # prettyVersioned :: CabalSpecVersion -> ExposedModule -> Doc Source # | |||||
Structured ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule Methods structure :: Proxy ExposedModule -> Structure Source # structureHash' :: Tagged ExposedModule MD5 | |||||
Binary ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule Methods put :: ExposedModule -> Put Source # get :: Get ExposedModule Source # putList :: [ExposedModule] -> Put Source # | |||||
NFData ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule Methods rnf :: ExposedModule -> () Source # | |||||
Generic ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule Associated Types
| |||||
Read ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule Methods readsPrec :: Int -> ReadS ExposedModule # readList :: ReadS [ExposedModule] # | |||||
Show ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule Methods showsPrec :: Int -> ExposedModule -> ShowS # show :: ExposedModule -> String # showList :: [ExposedModule] -> ShowS # | |||||
Eq ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule Methods (==) :: ExposedModule -> ExposedModule -> Bool # (/=) :: ExposedModule -> ExposedModule -> Bool # | |||||
type Rep ExposedModule Source # | |||||
Defined in Distribution.Types.ExposedModule type Rep ExposedModule = D1 ('MetaData "ExposedModule" "Distribution.Types.ExposedModule" "Cabal-syntax-3.14.1.0-e2ce" '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 | |
Fields
|
Instances
Parsec AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency Methods parsec :: CabalParsing m => m AbiDependency Source # | |||||
Pretty AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency Methods pretty :: AbiDependency -> Doc Source # prettyVersioned :: CabalSpecVersion -> AbiDependency -> Doc Source # | |||||
Structured AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency Methods structure :: Proxy AbiDependency -> Structure Source # structureHash' :: Tagged AbiDependency MD5 | |||||
Binary AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency Methods put :: AbiDependency -> Put Source # get :: Get AbiDependency Source # putList :: [AbiDependency] -> Put Source # | |||||
NFData AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency Methods rnf :: AbiDependency -> () Source # | |||||
Generic AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency Associated Types
| |||||
Read AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency Methods readsPrec :: Int -> ReadS AbiDependency # readList :: ReadS [AbiDependency] # | |||||
Show AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency Methods showsPrec :: Int -> AbiDependency -> ShowS # show :: AbiDependency -> String # showList :: [AbiDependency] -> ShowS # | |||||
Eq AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency Methods (==) :: AbiDependency -> AbiDependency -> Bool # (/=) :: AbiDependency -> AbiDependency -> Bool # | |||||
type Rep AbiDependency Source # | |||||
Defined in Distribution.Types.AbiDependency type Rep AbiDependency = D1 ('MetaData "AbiDependency" "Distribution.Types.AbiDependency" "Cabal-syntax-3.14.1.0-e2ce" '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 = fromString "Tester" }
>>>
fmap ($ ipi) $ showInstalledPackageInfoField "maintainer"
Just "maintainer: Tester"