bin-package-db-0.0.0.0: The GHC compiler's view of the GHC package database format

Copyright(c) The University of Glasgow 2009, Duncan Coutts 2014
Maintainerghc-devs@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

GHC.PackageDb

Description

This module provides the view of GHC's database of registered packages that is shared between GHC the compiler/library, and the ghc-pkg program. It defines the database format that is shared between GHC and ghc-pkg.

The database format, and this library are constructed so that GHC does not have to depend on the Cabal library. The ghc-pkg program acts as the gateway between the external package format (which is defined by Cabal) and the internal package format which is specialised just for GHC.

GHC the compiler only needs some of the information which is kept about registerd packages, such as module names, various paths etc. On the other hand ghc-pkg has to keep all the information from Cabal packages and be able to regurgitate it for users and other tools.

The first trick is that we duplicate some of the information in the package database. We essentially keep two versions of the datbase in one file, one version used only by ghc-pkg which keeps the full information (using the serialised form of the InstalledPackageInfo type defined by the Cabal library); and a second version written by ghc-pkg and read by GHC which has just the subset of information that GHC needs.

The second trick is that this module only defines in detail the format of the second version -- the bit GHC uses -- and the part managed by ghc-pkg is kept in the file but here we treat it as an opaque blob of data. That way this library avoids depending on Cabal.

Synopsis

Documentation

data InstalledPackageInfo instpkgid srcpkgid srcpkgname pkgkey modulename Source

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

Constructors

InstalledPackageInfo 

Fields

installedPackageId :: instpkgid
 
sourcePackageId :: srcpkgid
 
packageName :: srcpkgname
 
packageVersion :: Version
 
packageKey :: pkgkey
 
depends :: [instpkgid]
 
importDirs :: [FilePath]
 
hsLibraries :: [String]
 
extraLibraries :: [String]
 
extraGHCiLibraries :: [String]
 
libraryDirs :: [FilePath]
 
frameworks :: [String]
 
frameworkDirs :: [FilePath]
 
ldOptions :: [String]
 
ccOptions :: [String]
 
includes :: [String]
 
includeDirs :: [FilePath]
 
haddockInterfaces :: [FilePath]
 
haddockHTMLs :: [FilePath]
 
exposedModules :: [ExposedModule instpkgid modulename]
 
hiddenModules :: [modulename]
 
instantiatedWith :: [(modulename, OriginalModule instpkgid modulename)]
 
exposed :: Bool
 
trusted :: Bool
 

Instances

(Eq instpkgid, Eq srcpkgid, Eq srcpkgname, Eq pkgkey, Eq modulename) => Eq (InstalledPackageInfo instpkgid srcpkgid srcpkgname pkgkey modulename) 
(Show instpkgid, Show srcpkgid, Show srcpkgname, Show pkgkey, Show modulename) => Show (InstalledPackageInfo instpkgid srcpkgid srcpkgname pkgkey modulename) 
(BinaryStringRep a, BinaryStringRep b, BinaryStringRep c, BinaryStringRep d, BinaryStringRep e) => Binary (InstalledPackageInfo a b c d e) 

data ExposedModule instpkgid modulename Source

Represents a module name which is exported by a package, stored in the exposedModules field. A module export may be a reexport (in which case exposedReexport is filled in with the original source of the module), and may be a signature (in which case 'exposedSignature is filled in with what the signature was compiled against). Thus:

  • ExposedModule n Nothing Nothing represents an exposed module n which was defined in this package.
  • ExposedModule n (Just o) Nothing represents a reexported module n which was originally defined in o.
  • ExposedModule n Nothing (Just s) represents an exposed signature n which was compiled against the implementation s.
  • ExposedModule n (Just o) (Just s) represents a reexported signature which was originally defined in o and was compiled against the implementation s.

We use two Maybe data types instead of an ADT with four branches or four fields because this representation allows us to treat reexports/signatures uniformly.

Constructors

ExposedModule 

Fields

exposedName :: modulename
 
exposedReexport :: Maybe (OriginalModule instpkgid modulename)
 
exposedSignature :: Maybe (OriginalModule instpkgid modulename)
 

Instances

(Eq instpkgid, Eq modulename) => Eq (ExposedModule instpkgid modulename) 
(Show instpkgid, Show modulename) => Show (ExposedModule instpkgid modulename) 
(BinaryStringRep a, BinaryStringRep b) => Binary (ExposedModule a b) 

data OriginalModule instpkgid modulename Source

An original module is a fully-qualified module name (installed package ID plus module name) representing where a module was *originally* defined (i.e., the exposedReexport field of the original ExposedModule entry should be Nothing). Invariant: an OriginalModule never points to a reexport.

Constructors

OriginalModule 

Fields

originalPackageId :: instpkgid
 
originalModuleName :: modulename
 

Instances

(Eq instpkgid, Eq modulename) => Eq (OriginalModule instpkgid modulename) 
(Show instpkgid, Show modulename) => Show (OriginalModule instpkgid modulename) 
(BinaryStringRep a, BinaryStringRep b) => Binary (OriginalModule a b) 

readPackageDbForGhc :: (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c, BinaryStringRep d, BinaryStringRep e) => FilePath -> IO [InstalledPackageInfo a b c d e] Source

Read the part of the package DB that GHC is interested in.

readPackageDbForGhcPkg :: Binary pkgs => FilePath -> IO pkgs Source

Read the part of the package DB that ghc-pkg is interested in

Note that the Binary instance for ghc-pkg's representation of packages is not defined in this package. This is because ghc-pkg uses Cabal types (and Binary instances for these) which this package does not depend on.

writePackageDb :: (Binary pkgs, BinaryStringRep a, BinaryStringRep b, BinaryStringRep c, BinaryStringRep d, BinaryStringRep e) => FilePath -> [InstalledPackageInfo a b c d e] -> pkgs -> IO () Source

Write the whole of the package DB, both parts.