| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Unit.State
Description
Unit manipulation
Synopsis
- module GHC.Unit.Info
- data UnitState = UnitState {- unitInfoMap :: UnitInfoMap
- preloadClosure :: PreloadUnitClosure
- packageNameMap :: UniqFM PackageName UnitId
- wireMap :: Map UnitId UnitId
- unwireMap :: Map UnitId UnitId
- preloadUnits :: [UnitId]
- explicitUnits :: [(Unit, Maybe PackageArg)]
- homeUnitDepends :: [UnitId]
- moduleNameProvidersMap :: !ModuleNameProvidersMap
- pluginModuleNameProvidersMap :: !ModuleNameProvidersMap
- requirementContext :: Map ModuleName [InstantiatedModule]
- allowVirtualUnits :: !Bool
 
- type PreloadUnitClosure = UniqSet UnitId
- data UnitDatabase unit = UnitDatabase {- unitDatabasePath :: FilePath
- unitDatabaseUnits :: [GenUnitInfo unit]
 
- data UnitErr- = CloseUnitErr !UnitId !(Maybe UnitId)
- | PackageFlagErr !PackageFlag ![(UnitInfo, UnusableUnitReason)]
- | TrustFlagErr !TrustFlag ![(UnitInfo, UnusableUnitReason)]
 
- emptyUnitState :: UnitState
- initUnits :: Logger -> DynFlags -> Maybe [UnitDatabase UnitId] -> Set UnitId -> IO ([UnitDatabase UnitId], UnitState, HomeUnit, Maybe PlatformConstants)
- readUnitDatabases :: Logger -> UnitConfig -> IO [UnitDatabase UnitId]
- readUnitDatabase :: Logger -> UnitConfig -> FilePath -> IO (UnitDatabase UnitId)
- getUnitDbRefs :: UnitConfig -> IO [PkgDbRef]
- resolveUnitDatabase :: UnitConfig -> PkgDbRef -> IO (Maybe FilePath)
- listUnitInfo :: UnitState -> [UnitInfo]
- type UnitInfoMap = Map UnitId UnitInfo
- lookupUnit :: UnitState -> Unit -> Maybe UnitInfo
- lookupUnit' :: Bool -> UnitInfoMap -> PreloadUnitClosure -> Unit -> Maybe UnitInfo
- unsafeLookupUnit :: HasDebugCallStack => UnitState -> Unit -> UnitInfo
- lookupUnitId :: UnitState -> UnitId -> Maybe UnitInfo
- lookupUnitId' :: UnitInfoMap -> UnitId -> Maybe UnitInfo
- unsafeLookupUnitId :: HasDebugCallStack => UnitState -> UnitId -> UnitInfo
- lookupPackageName :: UnitState -> PackageName -> Maybe UnitId
- resolvePackageImport :: UnitState -> ModuleName -> PackageName -> Maybe UnitId
- improveUnit :: UnitState -> Unit -> Unit
- searchPackageId :: UnitState -> PackageId -> [UnitInfo]
- listVisibleModuleNames :: UnitState -> [ModuleName]
- lookupModuleInAllUnits :: UnitState -> ModuleName -> [(Module, UnitInfo)]
- lookupModuleWithSuggestions :: UnitState -> ModuleName -> PkgQual -> LookupResult
- lookupModulePackage :: UnitState -> ModuleName -> PkgQual -> Maybe [UnitInfo]
- lookupPluginModuleWithSuggestions :: UnitState -> ModuleName -> PkgQual -> LookupResult
- requirementMerges :: UnitState -> ModuleName -> [InstantiatedModule]
- data LookupResult- = LookupFound Module (UnitInfo, ModuleOrigin)
- | LookupMultiple [(Module, ModuleOrigin)]
- | LookupHidden [(Module, ModuleOrigin)] [(Module, ModuleOrigin)]
- | LookupUnusable [(Module, ModuleOrigin)]
- | LookupNotFound [ModuleSuggestion]
 
- data ModuleSuggestion
- data ModuleOrigin- = ModHidden
- | ModUnusable !UnusableUnit
- | ModOrigin { }
 
- data UnusableUnit = UnusableUnit {- uuUnit :: !Unit
- uuReason :: !UnusableUnitReason
- uuIsReexport :: !Bool
 
- data UnusableUnitReason
- pprReason :: SDoc -> UnusableUnitReason -> SDoc
- closeUnitDeps :: UnitInfoMap -> [(UnitId, Maybe UnitId)] -> MaybeErr UnitErr [UnitId]
- closeUnitDeps' :: UnitInfoMap -> [UnitId] -> [(UnitId, Maybe UnitId)] -> MaybeErr UnitErr [UnitId]
- mayThrowUnitErr :: MaybeErr UnitErr a -> IO a
- type ShHoleSubst = ModuleNameEnv Module
- renameHoleUnit :: UnitState -> ShHoleSubst -> Unit -> Unit
- renameHoleModule :: UnitState -> ShHoleSubst -> Module -> Module
- renameHoleUnit' :: UnitInfoMap -> PreloadUnitClosure -> ShHoleSubst -> Unit -> Unit
- renameHoleModule' :: UnitInfoMap -> PreloadUnitClosure -> ShHoleSubst -> Module -> Module
- instUnitToUnit :: UnitState -> InstantiatedUnit -> Unit
- instModuleToModule :: UnitState -> InstantiatedModule -> Module
- pprFlag :: PackageFlag -> SDoc
- pprUnits :: UnitState -> SDoc
- pprUnitsSimple :: UnitState -> SDoc
- pprUnitIdForUser :: UnitState -> UnitId -> SDoc
- pprUnitInfoForUser :: UnitInfo -> SDoc
- pprModuleMap :: ModuleNameProvidersMap -> SDoc
- pprWithUnitState :: UnitState -> SDoc -> SDoc
- unwireUnit :: UnitState -> Unit -> Unit
- implicitPackageDeps :: DynFlags -> [UnitId]
Documentation
module GHC.Unit.Info
Reading the package config, and processing cmdline args
Constructors
| UnitState | |
| Fields 
 | |
type PreloadUnitClosure = UniqSet UnitId Source #
data UnitDatabase unit Source #
Unit database
Constructors
| UnitDatabase | |
| Fields 
 | |
Instances
| Outputable u => Outputable (UnitDatabase u) Source # | |
| Defined in GHC.Unit.State Methods ppr :: UnitDatabase u -> SDoc Source # | |
Constructors
| CloseUnitErr !UnitId !(Maybe UnitId) | |
| PackageFlagErr !PackageFlag ![(UnitInfo, UnusableUnitReason)] | |
| TrustFlagErr !TrustFlag ![(UnitInfo, UnusableUnitReason)] | 
Instances
initUnits :: Logger -> DynFlags -> Maybe [UnitDatabase UnitId] -> Set UnitId -> IO ([UnitDatabase UnitId], UnitState, HomeUnit, Maybe PlatformConstants) 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 :: Logger -> UnitConfig -> IO [UnitDatabase UnitId] Source #
readUnitDatabase :: Logger -> 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, panicking 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, panicking if it is not found
lookupPackageName :: UnitState -> PackageName -> Maybe UnitId 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)
 This function is unsafe to use in general because it doesn't respect package
 visibility.
resolvePackageImport :: UnitState -> ModuleName -> PackageName -> Maybe UnitId Source #
Find the UnitId which an import qualified by a package import comes from.
 Compared to lookupPackageName, this function correctly accounts for visibility,
 renaming and thinning.
improveUnit :: UnitState -> Unit -> Unit Source #
Given a fully instantiated GenInstantiatedUnit, 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")
listVisibleModuleNames :: UnitState -> [ModuleName] Source #
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.
lookupModuleWithSuggestions :: UnitState -> ModuleName -> PkgQual -> LookupResult Source #
lookupModulePackage :: UnitState -> ModuleName -> PkgQual -> Maybe [UnitInfo] Source #
The package which the module **appears** to come from, this could be the one which reexports the module from it's original package. This function is currently only used for -Wunused-packages
requirementMerges :: UnitState -> ModuleName -> [InstantiatedModule] Source #
Return this list of requirement interfaces that need to be merged
 to form mod_name, or [] if this is not a requirement.
data LookupResult Source #
The result of performing a lookup
Constructors
| LookupFound Module (UnitInfo, ModuleOrigin) | 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 ModuleSuggestion Source #
data ModuleOrigin Source #
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 !UnusableUnit | Module is unavailable because the unit is unusable. | 
| ModOrigin | Module is public, and could have come from some places. | 
| Fields 
 | |
Instances
| Monoid ModuleOrigin Source # | |
| Defined in GHC.Unit.State Methods mempty :: ModuleOrigin Source # mappend :: ModuleOrigin -> ModuleOrigin -> ModuleOrigin Source # mconcat :: [ModuleOrigin] -> ModuleOrigin Source # | |
| Semigroup ModuleOrigin Source # | |
| Defined in GHC.Unit.State Methods (<>) :: ModuleOrigin -> ModuleOrigin -> ModuleOrigin Source # sconcat :: NonEmpty ModuleOrigin -> ModuleOrigin Source # stimes :: Integral b => b -> ModuleOrigin -> ModuleOrigin Source # | |
| Outputable ModuleOrigin Source # | |
| Defined in GHC.Unit.State Methods ppr :: ModuleOrigin -> SDoc Source # | |
data UnusableUnit Source #
A unusable unit module origin
Constructors
| UnusableUnit | |
| Fields 
 | |
data UnusableUnitReason Source #
The reason why a unit is unusable.
Constructors
| IgnoredWithFlag | We ignored it explicitly using  | 
| 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  | 
| 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
| Outputable UnusableUnitReason Source # | |
| Defined in GHC.Unit.State Methods ppr :: UnusableUnitReason -> SDoc Source # | |
closeUnitDeps :: UnitInfoMap -> [(UnitId, Maybe UnitId)] -> MaybeErr UnitErr [UnitId] Source #
Takes a list of UnitIds (and their "parent" dependency, used for error messages), and returns the list with dependencies included, in reverse dependency order (a units appears before those it depends on).
closeUnitDeps' :: UnitInfoMap -> [UnitId] -> [(UnitId, Maybe UnitId)] -> MaybeErr UnitErr [UnitId] Source #
Similar to closeUnitDeps but takes a list of already loaded units as an additional argument.
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 variables].
p[A=<A>] maps to p[A=<B>] with A=<B>.
renameHoleModule :: UnitState -> ShHoleSubst -> Module -> Module Source #
Substitutes holes in a GenModule.  NOT suitable for being called
 directly on a nameModule, see Note [Representation of module/name variables].
 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 GenInstantiatedUnit.
Return a UnitId which either wraps the GenInstantiatedUnit unchanged or
 references a matching installed unit.
See Note [VirtUnit to RealUnit improvement]
instModuleToModule :: UnitState -> InstantiatedModule -> Module Source #
Injects an InstantiatedModule to GenModule (see also
 instUnitToUnit.
Pretty-printing
pprFlag :: PackageFlag -> SDoc Source #
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)
pprUnitIdForUser :: UnitState -> UnitId -> SDoc Source #
Pretty-print a UnitId for the user.
Cabal packages may contain several components (programs, libraries, etc.). As far as GHC is concerned, installed package components ("units") are identified by an opaque UnitId string provided by Cabal. As the string contains a hash, we don't want to display it to users so GHC queries the database to retrieve some infos about the original source package (name, version, component name).
Instead we want to display: packagename-version[:componentname]
Component name is only displayed if it isn't the default library
To do this we need to query a unit database.
pprUnitInfoForUser :: UnitInfo -> SDoc Source #
pprModuleMap :: ModuleNameProvidersMap -> SDoc Source #
Show the mapping of modules to where they come from.
pprWithUnitState :: UnitState -> SDoc -> SDoc Source #
Print unit-ids with UnitInfo found in the given UnitState
Utils
implicitPackageDeps :: DynFlags -> [UnitId] Source #
Add package dependencies on the wired-in packages we use