| Copyright | (c) The University of Glasgow 2009 Duncan Coutts 2014 |
|---|---|
| Maintainer | ghc-devs@haskell.org |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
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
- data InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod = InstalledPackageInfo {
- unitId :: instunitid
- componentId :: compid
- instantiatedWith :: [(modulename, mod)]
- sourcePackageId :: srcpkgid
- packageName :: srcpkgname
- packageVersion :: Version
- sourceLibName :: Maybe srcpkgname
- abiHash :: String
- depends :: [instunitid]
- abiDepends :: [(instunitid, String)]
- importDirs :: [FilePath]
- hsLibraries :: [String]
- extraLibraries :: [String]
- extraGHCiLibraries :: [String]
- libraryDirs :: [FilePath]
- libraryDynDirs :: [FilePath]
- frameworks :: [String]
- frameworkDirs :: [FilePath]
- ldOptions :: [String]
- ccOptions :: [String]
- includes :: [String]
- includeDirs :: [FilePath]
- haddockInterfaces :: [FilePath]
- haddockHTMLs :: [FilePath]
- exposedModules :: [(modulename, Maybe mod)]
- hiddenModules :: [modulename]
- indefinite :: Bool
- exposed :: Bool
- trusted :: Bool
- data DbModule instunitid compid unitid modulename mod
- = DbModule {
- dbModuleUnitId :: unitid
- dbModuleName :: modulename
- | DbModuleVar {
- dbModuleVarName :: modulename
- = DbModule {
- data DbUnitId instunitid compid unitid modulename mod
- = DbUnitId compid [(modulename, mod)]
- | DbInstalledUnitId instunitid
- class BinaryStringRep a where
- fromStringRep :: ByteString -> a
- toStringRep :: a -> ByteString
- class DbUnitIdModuleRep instunitid compid unitid modulename mod | mod -> unitid, unitid -> mod, mod -> modulename, unitid -> compid, unitid -> instunitid where
- fromDbModule :: DbModule instunitid compid unitid modulename mod -> mod
- toDbModule :: mod -> DbModule instunitid compid unitid modulename mod
- fromDbUnitId :: DbUnitId instunitid compid unitid modulename mod -> unitid
- toDbUnitId :: unitid -> DbUnitId instunitid compid unitid modulename mod
- emptyInstalledPackageInfo :: RepInstalledPackageInfo a b c d e f g => InstalledPackageInfo a b c d e f g
- data PackageDbLock
- lockPackageDb :: FilePath -> IO PackageDbLock
- unlockPackageDb :: PackageDbLock -> IO ()
- data DbMode
- data DbOpenMode (mode :: DbMode) t where
- DbOpenReadOnly :: DbOpenMode DbReadOnly t
- DbOpenReadWrite :: t -> DbOpenMode DbReadWrite t
- isDbOpenReadMode :: DbOpenMode mode t -> Bool
- readPackageDbForGhc :: RepInstalledPackageInfo a b c d e f g => FilePath -> IO [InstalledPackageInfo a b c d e f g]
- readPackageDbForGhcPkg :: Binary pkgs => FilePath -> DbOpenMode mode t -> IO (pkgs, DbOpenMode mode PackageDbLock)
- writePackageDb :: (Binary pkgs, RepInstalledPackageInfo a b c d e f g) => FilePath -> [InstalledPackageInfo a b c d e f g] -> pkgs -> IO ()
Documentation
data InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod Source #
This is a subset of Cabal's InstalledPackageInfo , with just the bits
that GHC is interested in. See Cabal's documentation for a more detailed
description of all of the fields.
Constructors
Fields
- unitId :: instunitid
- componentId :: compid
- instantiatedWith :: [(modulename, mod)]
- sourcePackageId :: srcpkgid
- packageName :: srcpkgname
- packageVersion :: Version
- sourceLibName :: Maybe srcpkgname
- abiHash :: String
- depends :: [instunitid]
- abiDepends :: [(instunitid, String)]
Like
depends, but each dependency is annotated with the ABI hash we expect the dependency to respect. - importDirs :: [FilePath]
- hsLibraries :: [String]
- extraLibraries :: [String]
- extraGHCiLibraries :: [String]
- libraryDirs :: [FilePath]
- libraryDynDirs :: [FilePath]
- frameworks :: [String]
- frameworkDirs :: [FilePath]
- ldOptions :: [String]
- ccOptions :: [String]
- includes :: [String]
- includeDirs :: [FilePath]
- haddockInterfaces :: [FilePath]
- haddockHTMLs :: [FilePath]
- exposedModules :: [(modulename, Maybe mod)]
- :: [modulename]
- indefinite :: Bool
- exposed :: Bool
- trusted :: Bool
Instances
Instance details
Defined in GHC.PackageDb
Methods
(==) :: InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> Bool #
(/=) :: InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> Bool #
Instance details
Defined in GHC.PackageDb
Methods
showsPrec :: Int -> InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> ShowS #
show :: InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod -> String #
showList :: [InstalledPackageInfo compid srcpkgid srcpkgname instunitid unitid modulename mod] -> ShowS #
Instance details
Defined in GHC.PackageDb
Methods
put :: InstalledPackageInfo a b c d e f g -> Put #
get :: Get (InstalledPackageInfo a b c d e f g) #
putList :: [InstalledPackageInfo a b c d e f g] -> Put #
data DbModule instunitid compid unitid modulename mod Source #
ghc-boot's copy of Module, i.e. what is serialized to the database.
Use DbUnitIdModuleRep to convert it into an actual Module.
It has phantom type parameters as this is the most convenient way
to avoid undecidable instances.
Constructors
Fields
- dbModuleUnitId :: unitid
- dbModuleName :: modulename
Fields
- dbModuleVarName :: modulename
Instances
data DbUnitId instunitid compid unitid modulename mod Source #
ghc-boot's copy of UnitId, i.e. what is serialized to the database.
Use DbUnitIdModuleRep to convert it into an actual UnitId.
It has phantom type parameters as this is the most convenient way
to avoid undecidable instances.
Instances
class BinaryStringRep a where Source #
Instances
Instance details
Defined in Module
Methods
fromStringRep :: ByteString -> ComponentId Source #
toStringRep :: ComponentId -> ByteString Source #
Instance details
Defined in Module
Methods
fromStringRep :: ByteString -> ModuleName Source #
toStringRep :: ModuleName -> ByteString Source #
Instance details
Defined in PackageConfig
Methods
fromStringRep :: ByteString -> PackageName Source #
toStringRep :: PackageName -> ByteString Source #
Instance details
Defined in PackageConfig
Methods
class DbUnitIdModuleRep instunitid compid unitid modulename mod | mod -> unitid, unitid -> mod, mod -> modulename, unitid -> compid, unitid -> instunitid where Source #
A type-class for the types which can be converted into 'DbModule'/'DbUnitId'. There is only one type class because these types are mutually recursive. NB: The functional dependency helps out type inference in cases where types would be ambiguous.
Methods
fromDbModule :: DbModule instunitid compid unitid modulename mod -> mod Source #
toDbModule :: mod -> DbModule instunitid compid unitid modulename mod Source #
fromDbUnitId :: DbUnitId instunitid compid unitid modulename mod -> unitid Source #
toDbUnitId :: unitid -> DbUnitId instunitid compid unitid modulename mod Source #
Instances
Instance details
Defined in Module
Methods
fromDbModule :: DbModule InstalledUnitId ComponentId UnitId ModuleName Module -> Module Source #
toDbModule :: Module -> DbModule InstalledUnitId ComponentId UnitId ModuleName Module Source #
fromDbUnitId :: DbUnitId InstalledUnitId ComponentId UnitId ModuleName Module -> UnitId Source #
toDbUnitId :: UnitId -> DbUnitId InstalledUnitId ComponentId UnitId ModuleName Module Source #
emptyInstalledPackageInfo :: RepInstalledPackageInfo a b c d e f g => InstalledPackageInfo a b c d e f g Source #
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.
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.
Constructors
Instances
Instance details
Defined in GHC.PackageDb
Methods
fmap :: (a -> b) -> DbOpenMode mode a -> DbOpenMode mode b #
(<$) :: a -> DbOpenMode mode b -> DbOpenMode mode a #
Instance details
Defined in GHC.PackageDb
Methods
fold :: Monoid m => DbOpenMode mode m -> 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 #
Instance details
Defined in GHC.PackageDb
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) #
isDbOpenReadMode :: DbOpenMode mode t -> Bool Source #
readPackageDbForGhc :: RepInstalledPackageInfo a b c d e f g => FilePath -> IO [InstalledPackageInfo a b c d e f g] 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, RepInstalledPackageInfo a b c d e f g) => FilePath -> [InstalledPackageInfo a b c d e f g] -> pkgs -> IO () Source #
Write the whole of the package DB, both parts.