| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Unit.Module.ModIface
Synopsis
- type ModIface = ModIface_ 'ModIfaceFinal
- data ModIface_ (phase :: ModIfacePhase) = ModIface {- mi_module :: !Module
- mi_sig_of :: !(Maybe Module)
- mi_hsc_src :: !HscSource
- mi_deps :: Dependencies
- mi_usages :: [Usage]
- mi_exports :: ![IfaceExport]
- mi_used_th :: !Bool
- mi_fixities :: [(OccName, Fixity)]
- mi_warns :: Warnings GhcRn
- mi_anns :: [IfaceAnnotation]
- mi_decls :: [IfaceDeclExts phase]
- mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
- mi_globals :: !(Maybe GlobalRdrEnv)
- mi_insts :: [IfaceClsInst]
- mi_fam_insts :: [IfaceFamInst]
- mi_rules :: [IfaceRule]
- mi_hpc :: !AnyHpcUsage
- mi_trust :: !IfaceTrustInfo
- mi_trust_pkg :: !Bool
- mi_complete_matches :: ![IfaceCompleteMatch]
- mi_docs :: !(Maybe Docs)
- mi_final_exts :: !(IfaceBackendExts phase)
- mi_ext_fields :: !ExtensibleFields
- mi_src_hash :: !Fingerprint
 
- type PartialModIface = ModIface_ 'ModIfaceCore
- data ModIfaceBackend = ModIfaceBackend {- mi_iface_hash :: !Fingerprint
- mi_mod_hash :: !Fingerprint
- mi_flag_hash :: !Fingerprint
- mi_opt_hash :: !Fingerprint
- mi_hpc_hash :: !Fingerprint
- mi_plugin_hash :: !Fingerprint
- mi_orphan :: !WhetherHasOrphans
- mi_finsts :: !WhetherHasFamInst
- mi_exp_hash :: !Fingerprint
- mi_orphan_hash :: !Fingerprint
- mi_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn))
- mi_fix_fn :: !(OccName -> Maybe Fixity)
- mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
 
- type family IfaceDeclExts (phase :: ModIfacePhase) = decl | decl -> phase where ...
- type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where ...
- type IfaceExport = AvailInfo
- type WhetherHasOrphans = Bool
- type WhetherHasFamInst = Bool
- mi_boot :: ModIface -> IsBootInterface
- mi_fix :: ModIface -> OccName -> Fixity
- mi_semantic_module :: ModIface_ a -> Module
- mi_free_holes :: ModIface -> UniqDSet ModuleName
- mi_mnwib :: ModIface -> ModuleNameWithIsBoot
- renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
- emptyPartialModIface :: Module -> PartialModIface
- emptyFullModIface :: Module -> ModIface
- mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint)
- emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
- forceModIface :: ModIface -> IO ()
Documentation
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.
See Note [Strictness in ModIface] to learn about why some fields are strict and others are not.
Constructors
| ModIface | |
| Fields 
 | |
Instances
| Binary ModIface Source # | |
| (NFData (IfaceBackendExts phase), NFData (IfaceDeclExts phase)) => NFData (ModIface_ phase) Source # | |
| Defined in GHC.Unit.Module.ModIface | |
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 
 | |
Instances
| NFData ModIfaceBackend Source # | |
| Defined in GHC.Unit.Module.ModIface Methods rnf :: ModIfaceBackend -> () Source # | |
type family IfaceDeclExts (phase :: ModIfacePhase) = decl | 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 IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase 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.
emptyFullModIface :: Module -> ModIface Source #
mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint) Source #
Constructs cache for the mi_hash_fn field of a ModIface
emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint) Source #
forceModIface :: ModIface -> IO () Source #