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

GHC.Unit.Module.ModIface

Synopsis

Documentation

type ModIface = ModIface_ 'ModIfaceFinal Source #

data ModIface_ (phase :: ModIfacePhase) Source #

A ModIface plus a ModDetails summarises everything we know about a compiled module. The ModIface is the stuff *before* linking, and can be written out to an interface file. The 'ModDetails is after linking and can be completely recovered from just the ModIface.

When we read an interface file, we also construct a ModIface from it, except that we explicitly make the mi_decls and a few other fields empty; as when reading we consolidate the declarations etc. into a number of indexed maps and environments in the ExternalPackageState.

Constructors

ModIface 

Fields

  • mi_module :: !Module

    Name of the module we are for

  • mi_sig_of :: !(Maybe Module)

    Are we a sig of another mod?

  • mi_hsc_src :: !HscSource

    Boot? Signature?

  • mi_deps :: Dependencies

    The dependencies of the module. This is consulted for directly-imported modules, but not for anything else (hence lazy)

  • mi_usages :: [Usage]

    Usages; kept sorted so that it's easy to decide whether to write a new iface file (changing usages doesn't affect the hash of this module) NOT STRICT! we read this field lazily from the interface file It is *only* consulted by the recompilation checker

  • mi_exports :: ![IfaceExport]

    Exports Kept sorted by (mod,occ), to make version comparisons easier Records the modules that are the declaration points for things exported by this module, and the OccNames of those things

  • mi_used_th :: !Bool

    Module required TH splices when it was compiled. This disables recompilation avoidance (see #481).

  • mi_fixities :: [(OccName, Fixity)]

    Fixities NOT STRICT! we read this field lazily from the interface file

  • mi_warns :: Warnings

    Warnings NOT STRICT! we read this field lazily from the interface file

  • mi_anns :: [IfaceAnnotation]

    Annotations NOT STRICT! we read this field lazily from the interface file

  • mi_decls :: [IfaceDeclExts phase]

    Type, class and variable declarations The hash of an Id changes if its fixity or deprecations change (as well as its type of course) Ditto data constructors, class operations, except that the hash of the parent class/tycon changes

  • mi_globals :: !(Maybe GlobalRdrEnv)

    Binds all the things defined at the top level in the original source code for this module. which is NOT the same as mi_exports, nor mi_decls (which may contains declarations for things not actually defined by the user). Used for GHCi and for inspecting the contents of modules via the GHC API only.

    (We need the source file to figure out the top-level environment, if we didn't compile this module from source then this field contains Nothing).

    Strictly speaking this field should live in the HomeModInfo, but that leads to more plumbing.

  • mi_insts :: [IfaceClsInst]

    Sorted class instance

  • mi_fam_insts :: [IfaceFamInst]

    Sorted family instances

  • mi_rules :: [IfaceRule]

    Sorted rules

  • mi_hpc :: !AnyHpcUsage

    True if this program uses Hpc at any point in the program.

  • mi_trust :: !IfaceTrustInfo

    Safe Haskell Trust information for this module.

  • mi_trust_pkg :: !Bool

    Do we require the package this module resides in be trusted to trust this module? This is used for the situation where a module is Safe (so doesn't require the package be trusted itself) but imports some trustworthy modules from its own package (which does require its own package be trusted). See Note [Trust Own Package] in GHC.Rename.Names

  • mi_complete_matches :: [IfaceCompleteMatch]
     
  • mi_doc_hdr :: Maybe HsDocString

    Module header.

  • mi_decl_docs :: DeclDocMap

    Docs on declarations.

  • mi_arg_docs :: ArgDocMap

    Docs on arguments.

  • mi_final_exts :: !(IfaceBackendExts phase)

    Either () or ModIfaceBackend for a fully instantiated interface.

  • mi_ext_fields :: ExtensibleFields

    Additional optional fields, where the Map key represents the field name, resulting in a (size, serialized data) pair. Because the data is intended to be serialized through the internal Binary class (increasing compatibility with types using Name and FastString, such as HIE), this format is chosen over ByteStrings.

Instances

Instances details
Binary ModIface Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

(NFData (IfaceBackendExts phase), NFData (IfaceDeclExts phase)) => NFData (ModIface_ phase) Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: ModIface_ phase -> () #

type PartialModIface = ModIface_ 'ModIfaceCore Source #

data ModIfaceBackend Source #

Extends a PartialModIface with information which is either: * Computed after codegen * Or computed just before writing the iface to disk. (Hashes) In order to fully instantiate it.

Constructors

ModIfaceBackend 

Fields

type family IfaceDeclExts (phase :: ModIfacePhase) where ... Source #

Selects a IfaceDecl representation. For fully instantiated interfaces we also maintain a fingerprint, which is used for recompilation checks.

Equations

IfaceDeclExts 'ModIfaceCore = IfaceDecl 
IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl) 

type family IfaceBackendExts (phase :: ModIfacePhase) where ... Source #

Equations

IfaceBackendExts 'ModIfaceCore = () 
IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend 

type IfaceExport = AvailInfo Source #

The original names declared of a certain module that are exported

type WhetherHasOrphans = Bool Source #

Records whether a module has orphans. An "orphan" is one of:

  • An instance declaration in a module other than the definition module for one of the type constructors or classes in the instance head
  • A rewrite rule in a module other than the one defining the function in the head of the rule

type WhetherHasFamInst = Bool Source #

Does this module define family instances?

mi_boot :: ModIface -> IsBootInterface Source #

Old-style accessor for whether or not the ModIface came from an hs-boot file.

mi_fix :: ModIface -> OccName -> Fixity Source #

Lookups up a (possibly cached) fixity from a ModIface. If one cannot be found, defaultFixity is returned instead.

mi_semantic_module :: ModIface_ a -> Module Source #

The semantic module for this interface; e.g., if it's a interface for a signature, if mi_module is p[A=A]:A, mi_semantic_module will be A.

mi_free_holes :: ModIface -> UniqDSet ModuleName Source #

The "precise" free holes, e.g., the signatures that this ModIface depends on.

renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName Source #

Given a set of free holes, and a unit identifier, rename the free holes according to the instantiation of the unit identifier. For example, if we have A and B free, and our unit identity is p[A=C,B=impl:B], the renamed free holes are just C.

mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint) Source #

Constructs cache for the mi_hash_fn field of a ModIface