ghc-boot-8.0.0.20160421: Shared functionality between GHC and its boot libraries

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 srcpkgid srcpkgname unitid modulename Source #

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

Instances

(Eq srcpkgid, Eq srcpkgname, Eq unitid, Eq modulename) => Eq (InstalledPackageInfo srcpkgid srcpkgname unitid modulename) # 

Methods

(==) :: InstalledPackageInfo srcpkgid srcpkgname unitid modulename -> InstalledPackageInfo srcpkgid srcpkgname unitid modulename -> Bool #

(/=) :: InstalledPackageInfo srcpkgid srcpkgname unitid modulename -> InstalledPackageInfo srcpkgid srcpkgname unitid modulename -> Bool #

(Show srcpkgid, Show srcpkgname, Show unitid, Show modulename) => Show (InstalledPackageInfo srcpkgid srcpkgname unitid modulename) # 

Methods

showsPrec :: Int -> InstalledPackageInfo srcpkgid srcpkgname unitid modulename -> ShowS Source #

show :: InstalledPackageInfo srcpkgid srcpkgname unitid modulename -> String Source #

showList :: [InstalledPackageInfo srcpkgid srcpkgname unitid modulename] -> ShowS Source #

RepInstalledPackageInfo a b c d => Binary (InstalledPackageInfo a b c d) # 

data ExposedModule unitid 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). Thus:

  • ExposedModule n Nothing represents an exposed module n which was defined in this package.
  • ExposedModule n (Just o) represents a reexported module n which was originally defined in o.

We use a Maybe data types instead of an ADT with two branches because this representation allows us to treat reexports uniformly.

Constructors

ExposedModule 

Fields

Instances

(Eq unitid, Eq modulename) => Eq (ExposedModule unitid modulename) # 

Methods

(==) :: ExposedModule unitid modulename -> ExposedModule unitid modulename -> Bool #

(/=) :: ExposedModule unitid modulename -> ExposedModule unitid modulename -> Bool #

(Show unitid, Show modulename) => Show (ExposedModule unitid modulename) # 

Methods

showsPrec :: Int -> ExposedModule unitid modulename -> ShowS Source #

show :: ExposedModule unitid modulename -> String Source #

showList :: [ExposedModule unitid modulename] -> ShowS Source #

(BinaryStringRep a, BinaryStringRep b) => Binary (ExposedModule a b) # 

data OriginalModule unitid 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

Instances

(Eq unitid, Eq modulename) => Eq (OriginalModule unitid modulename) # 

Methods

(==) :: OriginalModule unitid modulename -> OriginalModule unitid modulename -> Bool #

(/=) :: OriginalModule unitid modulename -> OriginalModule unitid modulename -> Bool #

(Show unitid, Show modulename) => Show (OriginalModule unitid modulename) # 

Methods

showsPrec :: Int -> OriginalModule unitid modulename -> ShowS Source #

show :: OriginalModule unitid modulename -> String Source #

showList :: [OriginalModule unitid modulename] -> ShowS Source #

(BinaryStringRep a, BinaryStringRep b) => Binary (OriginalModule a b) # 

class BinaryStringRep a where Source #

Minimal complete definition

fromStringRep, toStringRep

emptyInstalledPackageInfo :: RepInstalledPackageInfo a b c d => InstalledPackageInfo a b c d Source #

readPackageDbForGhc :: RepInstalledPackageInfo a b c d => FilePath -> IO [InstalledPackageInfo a b c d] 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, RepInstalledPackageInfo a b c d) => FilePath -> [InstalledPackageInfo a b c d] -> pkgs -> IO () Source #

Write the whole of the package DB, both parts.