ghc-8.11.0.20200524: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Unit.State

Description

Package manipulation

Synopsis

Documentation

Reading the package config, and processing cmdline args

data PackageState Source #

Constructors

PackageState 

Fields

  • unitInfoMap :: UnitInfoMap

    A mapping of Unit to UnitInfo. This list is adjusted so that only valid packages are here. UnitInfo reflects what was stored *on disk*, except for the trusted flag, which is adjusted at runtime. (In particular, some packages in this map may have the exposed flag be False.)

  • packageNameMap :: Map PackageName IndefUnitId

    A mapping of PackageName to IndefUnitId. This is used when users refer to packages in Backpack includes.

  • unwireMap :: Map WiredUnitId WiredUnitId

    A mapping from wired in names to the original names from the package database.

  • preloadPackages :: [PreloadUnitId]

    The packages we're going to link in eagerly. This list should be in reverse dependency order; that is, a package is always mentioned before the packages it depends on.

  • explicitPackages :: [Unit]

    Packages which we explicitly depend on (from a command line flag). We'll use this to generate version macros.

  • moduleNameProvidersMap :: !ModuleNameProvidersMap

    This is a full map from ModuleName to all modules which may possibly be providing it. These providers may be hidden (but we'll still want to report them in error messages), or it may be an ambiguous import.

  • pluginModuleNameProvidersMap :: !ModuleNameProvidersMap

    A map, like moduleNameProvidersMap, but controlling plugin visibility.

  • requirementContext :: Map ModuleName [InstantiatedModule]

    A map saying, for each requirement, what interfaces must be merged together when we use them. For example, if our dependencies are p[A=A] and q[A=A,B=r[C=A]:B], then the interfaces to merge for A are p[A=A]:A, q[A=A,B=r[C=A]:B]:A and r[C=A]:C.

    There's an entry in this map for each hole in our home library.

data PackageDatabase unit Source #

Package database

data UnitInfoMap Source #

Map from UnitId to UnitInfo, plus the transitive closure of preload units.

initPackages :: DynFlags -> IO (DynFlags, [PreloadUnitId]) Source #

Read the package database files, and sets up various internal tables of package information, according to the package-related flags on the command-line (-package, -hide-package etc.)

Returns a list of packages to link in if we're doing dynamic linking. This list contains the packages that the user explicitly mentioned with -package flags.

initPackages can be called again subsequently after updating the packageFlags field of the DynFlags, and it will update the pkgState in DynFlags and return a list of packages to link in.

resolvePackageDatabase :: DynFlags -> PkgDbRef -> IO (Maybe FilePath) Source #

Return the path of a package database from a PkgDbRef. Return Nothing when the user database filepath is expected but the latter doesn't exist.

NB: This logic is reimplemented in Cabal, so if you change it, make sure you update Cabal. (Or, better yet, dump it in the compiler info so Cabal can use the info.)

listUnitInfoMap :: PackageState -> [UnitInfo] Source #

Get a list of entries from the package database. NB: be careful with this function, although all packages in this map are "visible", this does not imply that the exposed-modules of the package are available (they may have been thinned or renamed).

Querying the package config

lookupUnit :: DynFlags -> Unit -> Maybe UnitInfo Source #

Find the unit we know about with the given unit id, if any

lookupUnit' :: Bool -> UnitInfoMap -> Unit -> Maybe UnitInfo Source #

A more specialized interface, which takes a boolean specifying whether or not to look for on-the-fly renamed interfaces, and just a UnitInfoMap rather than a DynFlags (so it can be used while we're initializing DynFlags

lookupPackageName :: PackageState -> PackageName -> Maybe IndefUnitId Source #

Find the package we know about with the given package name (e.g. foo), if any (NB: there might be a locally defined unit name which overrides this)

improveUnit :: UnitInfoMap -> Unit -> Unit Source #

Given a fully instantiated GenInstantiatedUnit, improve it into a RealUnit if we can find it in the package database.

searchPackageId :: PackageState -> PackageId -> [UnitInfo] Source #

Search for packages with a given package ID (e.g. "foo-0.1")

unsafeGetUnitInfo :: HasDebugCallStack => DynFlags -> Unit -> UnitInfo Source #

Looks up the package with the given id in the package state, panicing if it is not found

lookupModuleInAllPackages :: DynFlags -> ModuleName -> [(Module, UnitInfo)] Source #

Takes a ModuleName, and if the module is in any package returns list of modules which take that name.

data LookupResult Source #

The result of performing a lookup

Constructors

LookupFound Module UnitInfo

Found the module uniquely, nothing else to do

LookupMultiple [(Module, ModuleOrigin)]

Multiple modules with the same name in scope

LookupHidden [(Module, ModuleOrigin)] [(Module, ModuleOrigin)]

No modules found, but there were some hidden ones with an exact name match. First is due to package hidden, second is due to module being hidden

LookupUnusable [(Module, ModuleOrigin)]

No modules found, but there were some unusable ones with an exact name match

LookupNotFound [ModuleSuggestion]

Nothing found, here are some suggested different names

data ModuleOrigin Source #

Package state is all stored in DynFlags, including the details of all packages, which packages are exposed, and which modules they provide.

The package state is computed by initPackages, and kept in DynFlags. It is influenced by various package flags:

  • -package pkg and -package-id pkg cause pkg to become exposed. If -hide-all-packages was not specified, these commands also cause all other packages with the same name to become hidden.
  • -hide-package pkg causes pkg to become hidden.
  • (there are a few more flags, check below for their semantics)

The package state has the following properties.

  • Let exposedPackages be the set of packages thus exposed. Let depExposedPackages be the transitive closure from exposedPackages of their dependencies.
  • When searching for a module from a preload import declaration, only the exposed modules in exposedPackages are valid.
  • When searching for a module from an implicit import, all modules from depExposedPackages are valid.
  • When linking in a compilation manager mode, we link in packages the program depends on (the compiler knows this list by the time it gets to the link step). Also, we link in all packages which were mentioned with preload -package flags on the command-line, or are a transitive dependency of same, or are "base"/"rts". The reason for this is that we might need packages which don't contain any Haskell modules, and therefore won't be discovered by the normal mechanism of dependency tracking.

Given a module name, there may be multiple ways it came into scope, possibly simultaneously. This data type tracks all the possible ways it could have come into scope. Warning: don't use the record functions, they're partial!

Constructors

ModHidden

Module is hidden, and thus never will be available for import. (But maybe the user didn't realize), so we'll still keep track of these modules.)

ModUnusable UnusablePackageReason

Module is unavailable because the package is unusable.

ModOrigin

Module is public, and could have come from some places.

Fields

  • fromOrigPackage :: Maybe Bool

    Just False means that this module is in someone's exported-modules list, but that package is hidden; Just True means that it is available; Nothing means neither applies.

  • fromExposedReexport :: [UnitInfo]

    Is the module available from a reexport of an exposed package? There could be multiple.

  • fromHiddenReexport :: [UnitInfo]

    Is the module available from a reexport of a hidden package?

  • fromPackageFlag :: Bool

    Did the module export come from a package flag? (ToDo: track more information.

data UnusablePackageReason Source #

The reason why a package is unusable.

Constructors

IgnoredWithFlag

We ignored it explicitly using -ignore-package.

BrokenDependencies [UnitId]

This package transitively depends on a package that was never present in any of the provided databases.

CyclicDependencies [UnitId]

This package transitively depends on a package involved in a cycle. Note that the list of UnitId reports the direct dependencies of this package that (transitively) depended on the cycle, and not the actual cycle itself (which we report separately at high verbosity.)

IgnoredDependencies [UnitId]

This package transitively depends on a package which was ignored.

ShadowedDependencies [UnitId]

This package transitively depends on a package which was shadowed by an ABI-incompatible package.

Instances

Instances details
Outputable UnusablePackageReason Source # 
Instance details

Defined in GHC.Unit.State

Inspecting the set of packages in scope

getPackageIncludePath :: DynFlags -> [PreloadUnitId] -> IO [String] Source #

Find all the include directories in these and the preload packages

getPackageLibraryPath :: DynFlags -> [PreloadUnitId] -> IO [String] Source #

Find all the library paths in these and the preload packages

getPackageLinkOpts :: DynFlags -> [PreloadUnitId] -> IO ([String], [String], [String]) Source #

Find all the link options in these and the preload packages, returning (package hs lib options, extra library options, other flags)

getPackageExtraCcOpts :: DynFlags -> [PreloadUnitId] -> IO [String] Source #

Find all the C-compiler options in these and the preload packages

getPackageFrameworkPath :: DynFlags -> [PreloadUnitId] -> IO [String] Source #

Find all the package framework paths in these and the preload packages

getPackageFrameworks :: DynFlags -> [PreloadUnitId] -> IO [String] Source #

Find all the package frameworks in these and the preload packages

getPreloadPackagesAnd :: DynFlags -> [PreloadUnitId] -> IO [UnitInfo] Source #

Find all the UnitInfo in both the preload packages from DynFlags and corresponding to the list of UnitInfos

getLibs :: DynFlags -> [PreloadUnitId] -> IO [(String, String)] Source #

Utils

updateIndefUnitId :: PackageState -> IndefUnitId -> IndefUnitId Source #

Update component ID details from the database

unwireUnit :: DynFlags -> Unit -> Unit Source #

Given a wired-in Unit, "unwire" it into the Unit that it was recorded as in the package database.

pprPackages :: PackageState -> SDoc Source #

Show (very verbose) package info

pprPackagesSimple :: PackageState -> SDoc Source #

Show simplified package info.

The idea is to only print package id, and any information that might be different from the package databases (exposure, trust)

pprModuleMap :: ModuleNameProvidersMap -> SDoc Source #

Show the mapping of modules to where they come from.

isIndefinite :: DynFlags -> Bool Source #

A little utility to tell if the thisPackage is indefinite (if it is not, we should never use on-the-fly renaming.)