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 HomeModImport Source #

Records the imports that we depend on from a home module, for recompilation checking.

See Note [When to recompile when export lists change?] in GHC.Iface.Recomp.

Constructors

HomeModImport 

Fields

data HomeModImportedAvails Source #

Records all the Avails we are importing from a home module.

Constructors

HMIA_Explicit

All import lists are explicit import lists, but some identifiers may still be implicitly imported, e.g. import M(a, b, T(..)).

In this case, recompilation is keyed by the names we are importing, with their Avail structure.

Fields

HMIA_Implicit

One import is a whole module import, or a import module M hiding(..) import.

In this case, recompilation is keyed on the hash of the exported avails of the module we are importing.

Fields

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