ghc-boot-9.2.1: 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.Unit.Database

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 registered 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 database 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 GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod Source #

Information about an unit (a unit is an installed module library).

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

Some types are left as parameters to be instantiated differently in ghc-pkg and in ghc itself.

Constructors

GenericUnitInfo 

Fields

  • unitId :: uid

    Unique unit identifier that is used during compilation (e.g. to generate symbols).

  • unitInstanceOf :: compid

    Identifier of an indefinite unit (i.e. with module holes) that this unit is an instance of.

  • unitInstantiations :: [(modulename, mod)]

    How this unit instantiates some of its module holes. Map hole module names to actual module

  • unitPackageId :: srcpkgid

    Source package identifier.

    Cabal instantiates this with Distribution.Types.PackageId.PackageId type which only contains the source package name and version. Notice that it doesn't contain the Hackage revision, nor any kind of hash.

  • unitPackageName :: srcpkgname

    Source package name

  • unitPackageVersion :: Version

    Source package version

  • unitComponentName :: Maybe srcpkgname

    Name of the component.

    Cabal supports more than one components (libraries, executables, testsuites) in the same package. Each component has a name except the default one (that can only be a library component) for which we use Nothing.

    GHC only deals with "library" components as they are the only kind of components that can be registered in a database and used by other modules.

  • unitAbiHash :: ShortText

    ABI hash used to avoid mixing up units compiled with different dependencies, compiler, options, etc.

  • unitDepends :: [uid]

    Identifiers of the units this one depends on

  • unitAbiDepends :: [(uid, ShortText)]

    Like unitDepends, but each dependency is annotated with the ABI hash we expect the dependency to respect.

  • unitImportDirs :: [FilePathST]

    Directories containing module interfaces

  • unitLibraries :: [ShortText]

    Names of the Haskell libraries provided by this unit

  • unitExtDepLibsSys :: [ShortText]

    Names of the external system libraries that this unit depends on. See also unitExtDepLibsGhc field.

  • unitExtDepLibsGhc :: [ShortText]

    Because of slight differences between the GHC dynamic linker (in GHC.Runtime.Linker) and the native system linker, some packages have to link with a different list of libraries when using GHC's. Examples include: libs that are actually gnu ld scripts, and the possibility that the .a libs do not exactly match the .so/.dll equivalents.

    If this field is set, then we use that instead of the unitExtDepLibsSys field.

  • unitLibraryDirs :: [FilePathST]

    Directories containing libraries provided by this unit. See also unitLibraryDynDirs.

    It seems to be used to store paths to external library dependencies too.

  • unitLibraryDynDirs :: [FilePathST]

    Directories containing the dynamic libraries provided by this unit. See also unitLibraryDirs.

    It seems to be used to store paths to external dynamic library dependencies too.

  • unitExtDepFrameworks :: [ShortText]

    Names of the external MacOS frameworks that this unit depends on.

  • unitExtDepFrameworkDirs :: [FilePathST]

    Directories containing MacOS frameworks that this unit depends on.

  • unitLinkerOptions :: [ShortText]

    Linker (e.g. ld) command line options

  • unitCcOptions :: [ShortText]

    C compiler options that needs to be passed to the C compiler when we compile some C code against this unit.

  • unitIncludes :: [ShortText]

    C header files that are required by this unit (provided by this unit or external)

  • unitIncludeDirs :: [FilePathST]

    Directories containing C header files that this unit depends on.

  • unitHaddockInterfaces :: [FilePathST]

    Paths to Haddock interface files for this unit

  • unitHaddockHTMLs :: [FilePathST]

    Paths to Haddock directories containing HTML files

  • unitExposedModules :: [(modulename, Maybe mod)]

    Modules exposed by the unit.

    A module can be re-exported from another package. In this case, we indicate the module origin in the second parameter.

  • unitHiddenModules :: [modulename]

    Hidden modules.

    These are useful for error reporting (e.g. if a hidden module is imported)

  • unitIsIndefinite :: Bool

    True if this unit has some module holes that need to be instantiated with real modules to make the unit usable (a.k.a. Backpack).

  • unitIsExposed :: Bool

    True if the unit is exposed. A unit could be installed in a database by "disabled" by not being exposed.

  • unitIsTrusted :: Bool

    True if the unit is trusted (cf Safe Haskell)

Instances

Instances details
Binary DbUnitInfo Source # 
Instance details

Defined in GHC.Unit.Database

(Eq uid, Eq compid, Eq modulename, Eq mod, Eq srcpkgid, Eq srcpkgname) => Eq (GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod) Source # 
Instance details

Defined in GHC.Unit.Database

Methods

(==) :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> Bool #

(/=) :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> Bool #

(Show uid, Show compid, Show modulename, Show mod, Show srcpkgid, Show srcpkgname) => Show (GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod) Source # 
Instance details

Defined in GHC.Unit.Database

Methods

showsPrec :: Int -> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> ShowS #

show :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> String #

showList :: [GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod] -> ShowS #

type DbUnitInfo = GenericUnitInfo ByteString ByteString ByteString ByteString ByteString DbModule Source #

ghc-boot's UnitInfo, serialized to the database.

data DbModule Source #

ghc-boot's Module, serialized to the database.

Instances

Instances details
Eq DbModule Source # 
Instance details

Defined in GHC.Unit.Database

Show DbModule Source # 
Instance details

Defined in GHC.Unit.Database

Binary DbModule Source # 
Instance details

Defined in GHC.Unit.Database

Methods

put :: DbModule -> Put #

get :: Get DbModule #

putList :: [DbModule] -> Put #

Binary DbUnitInfo Source # 
Instance details

Defined in GHC.Unit.Database

data DbInstUnitId Source #

ghc-boot's instantiated unit id, serialized to the database.

Constructors

DbInstUnitId ByteString [(ByteString, DbModule)]

Instantiated unit

DbUnitId ByteString

Uninstantiated unit

Instances

Instances details
Eq DbInstUnitId Source # 
Instance details

Defined in GHC.Unit.Database

Show DbInstUnitId Source # 
Instance details

Defined in GHC.Unit.Database

Binary DbInstUnitId Source # 
Instance details

Defined in GHC.Unit.Database

mapGenericUnitInfo :: (uid1 -> uid2) -> (cid1 -> cid2) -> (srcpkg1 -> srcpkg2) -> (srcpkgname1 -> srcpkgname2) -> (modname1 -> modname2) -> (mod1 -> mod2) -> GenericUnitInfo cid1 srcpkg1 srcpkgname1 uid1 modname1 mod1 -> GenericUnitInfo cid2 srcpkg2 srcpkgname2 uid2 modname2 mod2 Source #

Convert between GenericUnitInfo instances

Read and write

data DbMode Source #

Mode to open a package db in.

Constructors

DbReadOnly 
DbReadWrite 

data DbOpenMode (mode :: DbMode) t where Source #

DbOpenMode holds a value of type t but only in DbReadWrite mode. So it is like Maybe but with a type argument for the mode to enforce that the mode is used consistently.

Instances

Instances details
Functor (DbOpenMode mode) Source # 
Instance details

Defined in GHC.Unit.Database

Methods

fmap :: (a -> b) -> DbOpenMode mode a -> DbOpenMode mode b #

(<$) :: a -> DbOpenMode mode b -> DbOpenMode mode a #

Foldable (DbOpenMode mode) Source # 
Instance details

Defined in GHC.Unit.Database

Methods

fold :: Monoid m => DbOpenMode mode m -> m #

foldMap :: Monoid m => (a -> m) -> DbOpenMode mode a -> m #

foldMap' :: Monoid m => (a -> m) -> DbOpenMode mode a -> m #

foldr :: (a -> b -> b) -> b -> DbOpenMode mode a -> b #

foldr' :: (a -> b -> b) -> b -> DbOpenMode mode a -> b #

foldl :: (b -> a -> b) -> b -> DbOpenMode mode a -> b #

foldl' :: (b -> a -> b) -> b -> DbOpenMode mode a -> b #

foldr1 :: (a -> a -> a) -> DbOpenMode mode a -> a #

foldl1 :: (a -> a -> a) -> DbOpenMode mode a -> a #

toList :: DbOpenMode mode a -> [a] #

null :: DbOpenMode mode a -> Bool #

length :: DbOpenMode mode a -> Int #

elem :: Eq a => a -> DbOpenMode mode a -> Bool #

maximum :: Ord a => DbOpenMode mode a -> a #

minimum :: Ord a => DbOpenMode mode a -> a #

sum :: Num a => DbOpenMode mode a -> a #

product :: Num a => DbOpenMode mode a -> a #

Traversable (DbOpenMode mode) Source # 
Instance details

Defined in GHC.Unit.Database

Methods

traverse :: Applicative f => (a -> f b) -> DbOpenMode mode a -> f (DbOpenMode mode b) #

sequenceA :: Applicative f => DbOpenMode mode (f a) -> f (DbOpenMode mode a) #

mapM :: Monad m => (a -> m b) -> DbOpenMode mode a -> m (DbOpenMode mode b) #

sequence :: Monad m => DbOpenMode mode (m a) -> m (DbOpenMode mode a) #

readPackageDbForGhc :: FilePath -> IO [DbUnitInfo] Source #

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

readPackageDbForGhcPkg :: Binary pkgs => FilePath -> DbOpenMode mode t -> IO (pkgs, DbOpenMode mode PackageDbLock) 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.

If we open the package db in read only mode, we get its contents. Otherwise we additionally receive a PackageDbLock that represents a lock on the database, so that we can safely update it later.

writePackageDb :: Binary pkgs => FilePath -> [DbUnitInfo] -> pkgs -> IO () Source #

Write the whole of the package DB, both parts.

Locking

data PackageDbLock Source #

Represents a lock of a package db.

lockPackageDb :: FilePath -> IO PackageDbLock Source #

Acquire an exclusive lock related to package DB under given location.

unlockPackageDb :: PackageDbLock -> IO () Source #

Release the lock related to package DB.

Misc

mkMungePathUrl :: FilePathST -> FilePathST -> (FilePathST -> FilePathST, FilePathST -> FilePathST) Source #

mungeUnitInfoPaths :: FilePathST -> FilePathST -> GenericUnitInfo a b c d e f -> GenericUnitInfo a b c d e f Source #

Perform path/URL variable substitution as per the Cabal ${pkgroot} spec (http:/www.haskell.orgpipermaillibraries2009-May/011772.html) Paths/URLs can be relative to ${pkgroot} or ${pkgrooturl}. The "pkgroot" is the directory containing the package database.

Also perform a similar substitution for the older GHC-specific "$topdir" variable. The "topdir" is the location of the ghc installation (obtained from the -B option).