ghc-9.13: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Unit.Module.ModIface

Synopsis

Documentation

type ModIface = ModIface_ 'ModIfaceFinal Source #

data ModIface_ (phase :: ModIfacePhase) Source #

A ModIface summarises everything we know about a compiled module.

See Note [Structure of ModIface] for information about what belongs in each field.

See Note [Strictness in ModIface] to learn about why all the fields are lazy.

See Note [Private fields in ModIface] to learn why we don't export any of the fields.

Instances

Instances details
Binary ModIface Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

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

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: ModIface_ phase -> () Source #

set_mi_mod_info :: forall (phase :: ModIfacePhase). IfaceModInfo -> ModIface_ phase -> ModIface_ phase Source #

set_mi_module :: forall (phase :: ModIfacePhase). Module -> ModIface_ phase -> ModIface_ phase Source #

set_mi_sig_of :: forall (phase :: ModIfacePhase). Maybe Module -> ModIface_ phase -> ModIface_ phase Source #

set_mi_hsc_src :: forall (phase :: ModIfacePhase). HscSource -> ModIface_ phase -> ModIface_ phase Source #

set_mi_self_recomp :: forall (phase :: ModIfacePhase). Maybe IfaceSelfRecomp -> ModIface_ phase -> ModIface_ phase Source #

set_mi_hi_bytes :: forall (phase :: ModIfacePhase). IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase Source #

set_mi_deps :: forall (phase :: ModIfacePhase). Dependencies -> ModIface_ phase -> ModIface_ phase Source #

set_mi_exports :: forall (phase :: ModIfacePhase). [IfaceExport] -> ModIface_ phase -> ModIface_ phase Source #

set_mi_fixities :: forall (phase :: ModIfacePhase). [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase Source #

set_mi_warns :: forall (phase :: ModIfacePhase). IfaceWarnings -> ModIface_ phase -> ModIface_ phase Source #

set_mi_anns :: forall (phase :: ModIfacePhase). [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase Source #

set_mi_insts :: forall (phase :: ModIfacePhase). [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase Source #

set_mi_fam_insts :: forall (phase :: ModIfacePhase). [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase Source #

set_mi_rules :: forall (phase :: ModIfacePhase). [IfaceRule] -> ModIface_ phase -> ModIface_ phase Source #

set_mi_decls :: forall (phase :: ModIfacePhase). [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase Source #

set_mi_defaults :: forall (phase :: ModIfacePhase). [IfaceDefault] -> ModIface_ phase -> ModIface_ phase Source #

set_mi_simplified_core :: forall (phase :: ModIfacePhase). Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase Source #

set_mi_top_env :: forall (phase :: ModIfacePhase). IfaceTopEnv -> ModIface_ phase -> ModIface_ phase Source #

set_mi_trust :: forall (phase :: ModIfacePhase). IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase Source #

set_mi_trust_pkg :: forall (phase :: ModIfacePhase). Bool -> ModIface_ phase -> ModIface_ phase Source #

set_mi_complete_matches :: forall (phase :: ModIfacePhase). [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase Source #

set_mi_docs :: forall (phase :: ModIfacePhase). Maybe Docs -> ModIface_ phase -> ModIface_ phase Source #

set_mi_abi_hashes :: forall (phase :: ModIfacePhase). IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase Source #

set_mi_ext_fields :: forall (phase :: ModIfacePhase). ExtensibleFields -> ModIface_ phase -> ModIface_ phase Source #

set_mi_caches :: forall (phase :: ModIfacePhase). IfaceCache -> ModIface_ phase -> ModIface_ phase Source #

set_mi_decl_warn_fn :: forall (phase :: ModIfacePhase). (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase Source #

set_mi_export_warn_fn :: forall (phase :: ModIfacePhase). (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase Source #

set_mi_fix_fn :: forall (phase :: ModIfacePhase). (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase Source #

set_mi_hash_fn :: forall (phase :: ModIfacePhase). (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase Source #

data IfaceBinHandle (phase :: ModIfacePhase) where Source #

In-memory byte array representation of a ModIface.

See Note [Sharing of ModIface] for why we need this.

Constructors

PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore

A partial ModIface cannot be serialised to disk.

FullIfaceBinHandle :: !(Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal

Optional FullBinData that can be serialised to disk directly.

See Note [Private fields in ModIface] for when this fields needs to be cleared (e.g., set to Nothing).

type PartialModIface = ModIface_ 'ModIfaceCore Source #

data IfaceAbiHashes Source #

Extends a PartialModIface with hashes of the ABI.

  • The mi_mod_hash is the hash of the entire ABI
  • THe other fields are more specific hashes of parts of the ABI

Constructors

IfaceAbiHashes 

Fields

data IfaceSelfRecomp Source #

The information for a module which is only used when deciding whether to recompile itself.

See Note [Self recompilation information in interface files]

Constructors

IfaceSelfRecomp 

Fields

data IfaceCache Source #

Constructors

IfaceCache 

Fields

Instances

Instances details
NFData IfaceCache Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: IfaceCache -> () Source #

data IfaceSimplifiedCore Source #

The information needed to restart bytecode generation. Enabled by `-fwrite-if-simplified-core`.

Constructors

IfaceSimplifiedCore 

Fields

  • mi_sc_extra_decls :: [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]

    Extra variable definitions which are **NOT** exposed but when combined with mi_decls allows us to restart code generation. See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs]

  • mi_sc_foreign :: IfaceForeign

    Foreign stubs and files to supplement mi_extra_decls_. See Note [Foreign stubs and TH bytecode linking]

withSelfRecomp :: forall (phase :: ModIfacePhase) r. ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r Source #

type family IfaceDeclExts (phase :: ModIfacePhase) = (decl :: Type) | decl -> phase 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 IfaceAbiHashesExts (phase :: ModIfacePhase) = (bk :: Type) | bk -> phase where ... Source #

Equations

IfaceAbiHashesExts 'ModIfaceCore = () 
IfaceAbiHashesExts 'ModIfaceFinal = IfaceAbiHashes 

data IfacePublic_ (phase :: ModIfacePhase) Source #

The public interface of a module which are used by other modules when importing this module. The ABI of a module.

Constructors

IfacePublic 

Fields

Instances

Instances details
(NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: IfacePublic_ phase -> () Source #

type IfacePublic = IfacePublic_ 'ModIfaceFinal Source #

data IfaceModInfo Source #

Meta information about the module the interface file is for

Constructors

IfaceModInfo 

Fields

Instances

Instances details
NFData IfaceModInfo Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: IfaceModInfo -> () Source #

Binary IfaceModInfo Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

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?

data IfaceTopEnv Source #

Constructors

IfaceTopEnv 

Fields

Instances

Instances details
NFData IfaceTopEnv Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: IfaceTopEnv -> () Source #

Binary IfaceTopEnv Source # 
Instance details

Defined in GHC.Unit.Module.ModIface

data IfaceImport Source #

Instances

Instances details
NFData IfaceImport Source # 
Instance details

Defined in GHC.Iface.Syntax

Methods

rnf :: IfaceImport -> () Source #

Binary IfaceImport Source # 
Instance details

Defined in GHC.Iface.Syntax

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 :: forall (a :: ModIfacePhase). ModIface_ a -> Module Source #

mi_mod_info_semantic_module :: IfaceModInfo -> 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.

mi_flag_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags) Source #

mi_opt_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Fingerprint Source #

mi_hpc_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Fingerprint Source #

mi_plugin_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Fingerprint Source #

mi_src_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Fingerprint Source #

mi_usages :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe [Usage] Source #

mi_mod_hash :: ModIface -> Fingerprint Source #

Accessor for the module hash of the ABI from a ModIface.

mi_orphan :: ModIface -> WhetherHasOrphans Source #

Accessor for whether this module has orphans from a ModIface.

mi_finsts :: ModIface -> WhetherHasFamInst Source #

Accessor for whether this module has family instances from a ModIface.

mi_exp_hash :: ModIface -> Fingerprint Source #

Accessor for the hash of the export list from a ModIface.

mi_orphan_hash :: ModIface -> Fingerprint Source #

Accessor for the hash of orphan rules, class and family instances combined from a ModIface.

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