Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Dependencies and Usage of a module
Synopsis
- data Dependencies
- mkDependencies :: HomeUnit -> Module -> ImportAvails -> [Module] -> Dependencies
- noDependencies :: Dependencies
- dep_direct_mods :: Dependencies -> Set (UnitId, ModuleNameWithIsBoot)
- dep_direct_pkgs :: Dependencies -> Set UnitId
- dep_sig_mods :: Dependencies -> [ModuleName]
- dep_trusted_pkgs :: Dependencies -> Set UnitId
- dep_orphs :: Dependencies -> [Module]
- dep_plugin_pkgs :: Dependencies -> Set UnitId
- dep_finsts :: Dependencies -> [Module]
- dep_boot_mods :: Dependencies -> Set (UnitId, ModuleNameWithIsBoot)
- dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies
- dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies
- pprDeps :: UnitState -> Dependencies -> SDoc
- data Usage
- = UsagePackageModule { }
- | UsageHomeModule { }
- | UsageFile { }
- | UsageHomeModuleInterface { }
- | UsageMergedRequirement { }
- data ImportAvails = ImportAvails {}
Documentation
data Dependencies Source #
Dependency information about ALL modules and packages below this one
in the import hierarchy. This is the serialisable version of ImportAvails
.
Invariant: the dependencies of a module M
never includes M
.
Invariant: none of the lists contain duplicates.
Invariant: lists are ordered canonically (e.g. using stableModuleCmp)
See Note [Transitive Information in Dependencies]
Instances
Binary Dependencies Source # | |
Defined in GHC.Unit.Module.Deps put_ :: BinHandle -> Dependencies -> IO () Source # put :: BinHandle -> Dependencies -> IO (Bin Dependencies) Source # | |
Eq Dependencies Source # | |
Defined in GHC.Unit.Module.Deps (==) :: Dependencies -> Dependencies -> Bool # (/=) :: Dependencies -> Dependencies -> Bool # |
mkDependencies :: HomeUnit -> Module -> ImportAvails -> [Module] -> Dependencies Source #
Extract information from the rename and typecheck phases to produce a dependencies information for the module being compiled.
The fourth argument is a list of plugin modules.
dep_direct_mods :: Dependencies -> Set (UnitId, ModuleNameWithIsBoot) Source #
All home-package modules which are directly imported by this one. This may include modules from other units when using multiple home units
dep_direct_pkgs :: Dependencies -> Set UnitId Source #
All packages directly imported by this module
I.e. packages to which this module's direct imports belong.
Does not include other home units when using multiple home units.
Modules from these units will go in dep_direct_mods
dep_sig_mods :: Dependencies -> [ModuleName] Source #
Transitive closure of hsig files in the home package
dep_trusted_pkgs :: Dependencies -> Set UnitId Source #
dep_orphs :: Dependencies -> [Module] Source #
Transitive closure of orphan modules (whether home or external pkg).
(Possible optimization: don't include family
instance orphans as they are anyway included in
dep_finsts
. But then be careful about code
which relies on dep_orphs having the complete list!)
This does NOT include us, unlike imp_orphs
.
dep_plugin_pkgs :: Dependencies -> Set UnitId Source #
All units needed for plugins
dep_finsts :: Dependencies -> [Module] Source #
Transitive closure of depended upon modules which
contain family instances (whether home or external).
This is used by checkFamInstConsistency
. This
does NOT include us, unlike imp_finsts
. See Note
[The type family instance consistency story].
dep_boot_mods :: Dependencies -> Set (UnitId, ModuleNameWithIsBoot) Source #
All modules which have boot files below this one, and whether we should use the boot file or not. This information is only used to populate the eps_is_boot field. See Note [Structure of dep_boot_mods]
dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies Source #
Update module dependencies containing orphans (used by Backpack)
dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies Source #
Update module dependencies containing family instances (used by Backpack)
Records modules for which changes may force recompilation of this module See wiki: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/recompilation-avoidance
This differs from Dependencies. A module X may be in the dep_mods of this module (via an import chain) but if we don't use anything from X it won't appear in our Usage
UsagePackageModule | Module from another package |
| |
UsageHomeModule | Module from the current package |
| |
UsageFile | A file upon which the module depends, e.g. a CPP #include, or using TH's
|
| |
UsageHomeModuleInterface | |
| |
UsageMergedRequirement | A requirement which was merged into this one. |
|
data ImportAvails Source #
ImportAvails
summarises what was imported from where, irrespective of
whether the imported things are actually used or not. It is used:
- when processing the export list,
- when constructing usage info for the interface file,
- to identify the list of directly imported modules for initialisation purposes and for optimised overlap checking of family instances,
- when figuring out what things are really unused
ImportAvails | |
|