Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- type ModIface = ModIface_ 'ModIfaceFinal
- data ModIface_ (phase :: ModIfacePhase)
- pattern ModIface :: Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> ModIface_ phase
- restoreFromOldModIface :: forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase -> ModIface_ phase
- addSourceFingerprint :: forall (phase :: ModIfacePhase). Fingerprint -> ModIface_ phase -> ModIface_ phase
- set_mi_module :: forall (phase :: ModIfacePhase). Module -> ModIface_ phase -> ModIface_ phase
- set_mi_sig_of :: forall (phase :: ModIfacePhase). Maybe Module -> ModIface_ phase -> ModIface_ phase
- set_mi_hsc_src :: forall (phase :: ModIfacePhase). HscSource -> ModIface_ phase -> ModIface_ phase
- set_mi_src_hash :: forall (phase :: ModIfacePhase). Fingerprint -> ModIface_ phase -> ModIface_ phase
- set_mi_hi_bytes :: forall (phase :: ModIfacePhase). IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase
- set_mi_deps :: forall (phase :: ModIfacePhase). Dependencies -> ModIface_ phase -> ModIface_ phase
- set_mi_usages :: forall (phase :: ModIfacePhase). [Usage] -> ModIface_ phase -> ModIface_ phase
- set_mi_exports :: forall (phase :: ModIfacePhase). [IfaceExport] -> ModIface_ phase -> ModIface_ phase
- set_mi_used_th :: forall (phase :: ModIfacePhase). Bool -> ModIface_ phase -> ModIface_ phase
- set_mi_fixities :: forall (phase :: ModIfacePhase). [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase
- set_mi_warns :: forall (phase :: ModIfacePhase). IfaceWarnings -> ModIface_ phase -> ModIface_ phase
- set_mi_anns :: forall (phase :: ModIfacePhase). [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase
- set_mi_insts :: forall (phase :: ModIfacePhase). [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase
- set_mi_fam_insts :: forall (phase :: ModIfacePhase). [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase
- set_mi_rules :: forall (phase :: ModIfacePhase). [IfaceRule] -> ModIface_ phase -> ModIface_ phase
- set_mi_decls :: forall (phase :: ModIfacePhase). [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase
- set_mi_defaults :: forall (phase :: ModIfacePhase). [IfaceDefault] -> ModIface_ phase -> ModIface_ phase
- set_mi_extra_decls :: forall (phase :: ModIfacePhase). Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase
- set_mi_foreign :: forall (phase :: ModIfacePhase). IfaceForeign -> ModIface_ phase -> ModIface_ phase
- set_mi_top_env :: forall (phase :: ModIfacePhase). Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase
- set_mi_hpc :: forall (phase :: ModIfacePhase). AnyHpcUsage -> ModIface_ phase -> ModIface_ phase
- set_mi_trust :: forall (phase :: ModIfacePhase). IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase
- set_mi_trust_pkg :: forall (phase :: ModIfacePhase). Bool -> ModIface_ phase -> ModIface_ phase
- set_mi_complete_matches :: forall (phase :: ModIfacePhase). [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase
- set_mi_docs :: forall (phase :: ModIfacePhase). Maybe Docs -> ModIface_ phase -> ModIface_ phase
- set_mi_final_exts :: forall (phase :: ModIfacePhase). IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase
- set_mi_ext_fields :: forall (phase :: ModIfacePhase). ExtensibleFields -> ModIface_ phase -> ModIface_ phase
- completePartialModIface :: PartialModIface -> [(Fingerprint, IfaceDecl)] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIfaceBackend -> ModIface
- data IfaceBinHandle (phase :: ModIfacePhase) where
- PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore
- FullIfaceBinHandle :: !(Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal
- 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_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn))
- mi_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn))
- mi_fix_fn :: !(OccName -> Maybe Fixity)
- mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
- type family IfaceDeclExts (phase :: ModIfacePhase) = (decl :: Type) | decl -> phase where ...
- type family IfaceBackendExts (phase :: ModIfacePhase) = (bk :: Type) | bk -> phase where ...
- type IfaceExport = AvailInfo
- type WhetherHasOrphans = Bool
- type WhetherHasFamInst = Bool
- data IfaceTopEnv = IfaceTopEnv {}
- data IfaceImport = IfaceImport ImpDeclSpec ImpIfaceList
- mi_boot :: ModIface -> IsBootInterface
- mi_fix :: ModIface -> OccName -> Fixity
- mi_semantic_module :: forall (a :: ModIfacePhase). 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.
See Note [Private fields in ModIface] to learn why we don't export any of the fields.
Instances
Binary ModIface Source # | |
(NFData (IfaceBackendExts phase), NFData (IfaceDeclExts phase)) => NFData (ModIface_ phase) Source # | |
Defined in GHC.Unit.Module.ModIface |
pattern ModIface :: Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IfaceForeign -> [IfaceDefault] -> Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> ModIface_ phase Source #
restoreFromOldModIface :: forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase -> ModIface_ phase Source #
Copy fields that aren't serialised to disk to the new ModIface_
.
This includes especially hashes that are usually stored in the interface
file header and mi_top_env
.
We need this function after calling shareIface
, to make sure the
ModIface_
doesn't lose any information. This function does not discard
the in-memory byte array buffer mi_hi_bytes
.
addSourceFingerprint :: forall (phase :: ModIfacePhase). Fingerprint -> ModIface_ phase -> ModIface_ phase Source #
Add a source fingerprint to a ModIface_
without invalidating the byte array
buffer mi_hi_bytes
.
This is a variant of set_mi_src_hash
which does invalidate the buffer.
The mi_src_hash
is computed outside of ModIface_
based on the ModSummary
.
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_src_hash :: forall (phase :: ModIfacePhase). Fingerprint -> 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_usages :: forall (phase :: ModIfacePhase). [Usage] -> ModIface_ phase -> ModIface_ phase Source #
set_mi_exports :: forall (phase :: ModIfacePhase). [IfaceExport] -> ModIface_ phase -> ModIface_ phase Source #
set_mi_used_th :: forall (phase :: ModIfacePhase). Bool -> 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_extra_decls :: forall (phase :: ModIfacePhase). Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase Source #
set_mi_foreign :: forall (phase :: ModIfacePhase). IfaceForeign -> ModIface_ phase -> ModIface_ phase Source #
set_mi_top_env :: forall (phase :: ModIfacePhase). Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase Source #
set_mi_hpc :: forall (phase :: ModIfacePhase). AnyHpcUsage -> 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_final_exts :: forall (phase :: ModIfacePhase). IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase Source #
set_mi_ext_fields :: forall (phase :: ModIfacePhase). ExtensibleFields -> ModIface_ phase -> ModIface_ phase Source #
completePartialModIface :: PartialModIface -> [(Fingerprint, IfaceDecl)] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIfaceBackend -> ModIface Source #
Given a PartialModIface
, turn it into a ModIface
by completing
missing fields.
data IfaceBinHandle (phase :: ModIfacePhase) where Source #
In-memory byte array representation of a ModIface
.
See Note [Sharing of ModIface] for why we need this.
PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore | A partial |
FullIfaceBinHandle :: !(Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal | Optional See Note [Private fields in ModIface] for when this fields needs to be cleared
(e.g., set to |
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.
ModIfaceBackend | |
|
Instances
NFData ModIfaceBackend Source # | |
Defined in GHC.Unit.Module.ModIface rnf :: ModIfaceBackend -> () 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.
IfaceDeclExts 'ModIfaceCore = IfaceDecl | |
IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl) |
type family IfaceBackendExts (phase :: ModIfacePhase) = (bk :: Type) | bk -> phase where ... Source #
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?
data IfaceTopEnv Source #
IfaceTopEnv | |
|
Instances
NFData IfaceTopEnv Source # | |
Defined in GHC.Unit.Module.ModIface rnf :: IfaceTopEnv -> () Source # |
data IfaceImport Source #
Instances
NFData IfaceImport Source # | |
Defined in GHC.Iface.Syntax rnf :: IfaceImport -> () Source # |
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 #
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 #