ghc-9.13: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Unit.Module.Deps

Description

Dependencies and Usage of a module

Synopsis

Documentation

data Dependencies where 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

Instances details
NFData Dependencies Source # 
Instance details

Defined in GHC.Unit.Module.Deps

Methods

rnf :: Dependencies -> () Source #

Binary Dependencies Source # 
Instance details

Defined in GHC.Unit.Module.Deps

Eq Dependencies Source # 
Instance details

Defined in GHC.Unit.Module.Deps

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)

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.

pprDeps :: UnitState -> Dependencies -> SDoc Source #

Pretty-print unit dependencies

data Usage Source #

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

Constructors

UsagePackageModule

Module from another package

Fields

UsageHomeModule

Module from the current package

Fields

UsageFile

A file upon which the module depends, e.g. a CPP #include, or using TH's addDependentFile

Fields

UsageHomeModuleInterface 

Fields

UsageMergedRequirement

A requirement which was merged into this one.

Fields

Instances

Instances details
NFData Usage Source # 
Instance details

Defined in GHC.Unit.Module.Deps

Methods

rnf :: Usage -> () Source #

Binary Usage Source # 
Instance details

Defined in GHC.Unit.Module.Deps

Eq Usage Source # 
Instance details

Defined in GHC.Unit.Module.Deps

Methods

(==) :: Usage -> Usage -> Bool #

(/=) :: Usage -> Usage -> Bool #

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

Constructors

ImportAvails 

Fields

  • imp_mods :: ImportedMods

    Domain is all directly-imported modules

    See the documentation on ImportedModsVal in GHC.Unit.Module.Imported for the meaning of the fields.

    We need a full ModuleEnv rather than a ModuleNameEnv here, because we might be importing modules of the same name from different packages. (currently not the case, but might be in the future).

  • imp_direct_dep_mods :: InstalledModuleEnv ModuleNameWithIsBoot

    Home-package modules directly imported by the module being compiled.

  • imp_dep_direct_pkgs :: Set UnitId

    Packages directly needed by the module being compiled

  • imp_trust_own_pkg :: Bool

    Do we require that our own package is trusted? This is to handle efficiently the case where a Safe module imports a Trustworthy module that resides in the same package as it. See Note [Trust Own Package] in GHC.Rename.Names

  • imp_trust_pkgs :: Set UnitId

    This records the packages the current module needs to trust for Safe Haskell compilation to succeed. A package is required to be trusted if we are dependent on a trustworthy module in that package. See Note [Tracking Trust Transitively] in GHC.Rename.Names

  • imp_boot_mods :: InstalledModuleEnv ModuleNameWithIsBoot

    Domain is all modules which have hs-boot files, and whether we should import the boot version of interface file. Only used in one-shot mode to populate eps_is_boot.

  • imp_sig_mods :: [ModuleName]

    Signature modules below this one

  • imp_orphs :: [Module]

    Orphan modules below us in the import tree (and maybe including us for imported modules)

  • imp_finsts :: [Module]

    Family instance modules below us in the import tree (and maybe including us for imported modules)