ghc-lib-parser-9.0.1.20210324: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Unit.State

Description

Unit manipulation

Synopsis

Documentation

Reading the package config, and processing cmdline args

data UnitState Source #

Constructors

UnitState 

Fields

  • unitInfoMap :: UnitInfoMap

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

  • preloadClosure :: PreloadUnitClosure

    The set of transitively reachable units according to the explicitly provided command line arguments. A fully instantiated VirtUnit may only be replaced by a RealUnit from this set. See Note [VirtUnit to RealUnit improvement]

  • packageNameMap :: Map PackageName IndefUnitId

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

  • wireMap :: Map UnitId UnitId

    A mapping from database unit keys to wired in unit ids.

  • unwireMap :: Map UnitId UnitId

    A mapping from wired in unit ids to unit keys from the database.

  • preloadUnits :: [UnitId]

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

  • explicitUnits :: [Unit]

    Units 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.

  • allowVirtualUnits :: !Bool

    Indicate if we can instantiate units on-the-fly.

    This should only be true when we are type-checking an indefinite unit. See Note [About units] in GHC.Unit.

data UnitDatabase unit Source #

Unit database

initUnits :: DynFlags -> IO DynFlags Source #

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

initUnits can be called again subsequently after updating the packageFlags field of the DynFlags, and it will update the unitState in DynFlags.

readUnitDatabases :: (Int -> SDoc -> IO ()) -> UnitConfig -> IO [UnitDatabase UnitId] Source #

readUnitDatabase :: (Int -> SDoc -> IO ()) -> UnitConfig -> FilePath -> IO (UnitDatabase UnitId) Source #

getUnitDbRefs :: UnitConfig -> IO [PkgDbRef] Source #

resolveUnitDatabase :: UnitConfig -> 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.)

listUnitInfo :: UnitState -> [UnitInfo] Source #

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

Querying the package config

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

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

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

A more specialized interface, which doesn't require a UnitState (so it can be used while we're initializing DynFlags)

Parameters: * a boolean specifying whether or not to look for on-the-fly renamed interfaces * a UnitInfoMap * a PreloadUnitClosure

unsafeLookupUnit :: HasDebugCallStack => UnitState -> Unit -> UnitInfo Source #

Looks up the given unit in the unit state, panicing if it is not found

lookupUnitId :: UnitState -> UnitId -> Maybe UnitInfo Source #

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

lookupUnitId' :: UnitInfoMap -> UnitId -> Maybe UnitInfo Source #

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

unsafeLookupUnitId :: HasDebugCallStack => UnitState -> UnitId -> UnitInfo Source #

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

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

Find the unit 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 :: UnitState -> Unit -> Unit Source #

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

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

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

lookupModuleInAllUnits :: UnitState -> 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 #

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

The unit state is computed by initUnits, and kept in DynFlags. It is influenced by various command-line 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 unit state has the following properties.

  • Let exposedUnits be the set of packages thus exposed. Let depExposedUnits be the transitive closure from exposedUnits of their dependencies.
  • When searching for a module from a preload import declaration, only the exposed modules in exposedUnits are valid.
  • When searching for a module from an implicit import, all modules from depExposedUnits 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 UnusableUnitReason

Module is unavailable because the package is unusable.

ModOrigin

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

Fields

  • fromOrigUnit :: 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 UnusableUnitReason Source #

The reason why a unit is unusable.

Constructors

IgnoredWithFlag

We ignored it explicitly using -ignore-package.

BrokenDependencies [UnitId]

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

CyclicDependencies [UnitId]

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

IgnoredDependencies [UnitId]

This unit transitively depends on a unit which was ignored.

ShadowedDependencies [UnitId]

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

Instances

Instances details
Outputable UnusableUnitReason Source # 
Instance details

Defined in GHC.Unit.State

Inspecting the set of packages in scope

getUnitIncludePath :: DynFlags -> [UnitId] -> IO [String] Source #

Find all the include directories in these and the preload packages

getUnitLibraryPath :: DynFlags -> [UnitId] -> IO [String] Source #

Find all the library paths in these and the preload packages

getUnitLinkOpts :: DynFlags -> [UnitId] -> 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)

getUnitExtraCcOpts :: DynFlags -> [UnitId] -> IO [String] Source #

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

getUnitFrameworkPath :: DynFlags -> [UnitId] -> IO [String] Source #

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

getUnitFrameworks :: DynFlags -> [UnitId] -> IO [String] Source #

Find all the package frameworks in these and the preload packages

getPreloadUnitsAnd :: DynFlags -> [UnitId] -> IO [UnitInfo] Source #

Lookup UnitInfo for every preload unit, for every unit used to instantiate the current unit, and for every unit explicitly passed in the given list of UnitId.

Module hole substitution

type ShHoleSubst = ModuleNameEnv Module Source #

Substitution on module variables, mapping module names to module identifiers.

renameHoleUnit :: UnitState -> ShHoleSubst -> Unit -> Unit Source #

Substitutes holes in a Unit, suitable for renaming when an include occurs; see Note [Representation of module/name variable].

p[A=<A>] maps to p[A=<B>] with A=<B>.

renameHoleModule :: UnitState -> ShHoleSubst -> Module -> Module Source #

Substitutes holes in a Module. NOT suitable for being called directly on a nameModule, see Note [Representation of module/name variable]. p[A=<A>]:B maps to p[A=q():A]:B with A=q():A; similarly, <A> maps to q():A.

renameHoleUnit' :: UnitInfoMap -> PreloadUnitClosure -> ShHoleSubst -> Unit -> Unit Source #

Like 'renameHoleUnit, but requires only ClosureUnitInfoMap so it can be used by GHC.Unit.State.

renameHoleModule' :: UnitInfoMap -> PreloadUnitClosure -> ShHoleSubst -> Module -> Module Source #

Like renameHoleModule, but requires only ClosureUnitInfoMap so it can be used by GHC.Unit.State.

instUnitToUnit :: UnitState -> InstantiatedUnit -> Unit Source #

Check the database to see if we already have an installed unit that corresponds to the given InstantiatedUnit.

Return a UnitId which either wraps the InstantiatedUnit unchanged or references a matching installed unit.

See Note [VirtUnit to RealUnit improvement]

Utils

updateIndefUnitId :: UnitState -> IndefUnitId -> IndefUnitId Source #

Update component ID details from the database

unwireUnit :: UnitState -> Unit -> Unit Source #

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

pprUnits :: UnitState -> SDoc Source #

Show (very verbose) package info

pprUnitsSimple :: UnitState -> SDoc Source #

Show simplified unit 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.

homeUnitIsIndefinite :: DynFlags -> Bool Source #

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

homeUnitIsDefinite :: DynFlags -> Bool Source #

A little utility to tell if the home unit is definite (if it is, we should never use on-the-fly renaming.)