Safe Haskell | None |
---|---|
Language | GHC2021 |
GHC.Unit.Module.ModIface
Synopsis
- type ModIface = ModIface_ 'ModIfaceFinal
- data ModIface_ (phase :: ModIfacePhase)
- pattern ModIface :: IfaceModInfo -> Module -> Maybe Module -> HscSource -> Fingerprint -> Dependencies -> IfacePublic_ phase -> [IfaceExport] -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe IfaceSimplifiedCore -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceAbiHashesExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe IfaceSelfRecomp -> (OccName -> Maybe Fixity) -> (OccName -> Maybe (OccName, Fingerprint)) -> (OccName -> Maybe (WarningTxt GhcRn)) -> (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase
- set_mi_mod_info :: forall (phase :: ModIfacePhase). IfaceModInfo -> 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_self_recomp :: forall (phase :: ModIfacePhase). Maybe IfaceSelfRecomp -> 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_exports :: forall (phase :: ModIfacePhase). [IfaceExport] -> 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_simplified_core :: forall (phase :: ModIfacePhase). Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase
- set_mi_top_env :: forall (phase :: ModIfacePhase). IfaceTopEnv -> 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_abi_hashes :: forall (phase :: ModIfacePhase). IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase
- set_mi_ext_fields :: forall (phase :: ModIfacePhase). ExtensibleFields -> ModIface_ phase -> ModIface_ phase
- set_mi_caches :: forall (phase :: ModIfacePhase). IfaceCache -> ModIface_ phase -> ModIface_ phase
- set_mi_decl_warn_fn :: forall (phase :: ModIfacePhase). (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase
- set_mi_export_warn_fn :: forall (phase :: ModIfacePhase). (Name -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase
- set_mi_fix_fn :: forall (phase :: ModIfacePhase). (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase
- set_mi_hash_fn :: forall (phase :: ModIfacePhase). (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase
- completePartialModIface :: PartialModIface -> Fingerprint -> [(Fingerprint, IfaceDecl)] -> Maybe IfaceSimplifiedCore -> IfaceAbiHashes -> IfaceCache -> ModIface
- data IfaceBinHandle (phase :: ModIfacePhase) where
- PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore
- FullIfaceBinHandle :: !(Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal
- type PartialModIface = ModIface_ 'ModIfaceCore
- data IfaceAbiHashes = IfaceAbiHashes {}
- data IfaceSelfRecomp = IfaceSelfRecomp {}
- data IfaceCache = IfaceCache {
- mi_cache_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn))
- mi_cache_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn))
- mi_cache_fix_fn :: !(OccName -> Maybe Fixity)
- mi_cache_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
- data IfaceSimplifiedCore = IfaceSimplifiedCore {}
- withSelfRecomp :: forall (phase :: ModIfacePhase) r. ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r
- type family IfaceDeclExts (phase :: ModIfacePhase) = (decl :: Type) | decl -> phase where ...
- type family IfaceAbiHashesExts (phase :: ModIfacePhase) = (bk :: Type) | bk -> phase where ...
- type IfaceExport = AvailInfo
- data IfacePublic_ (phase :: ModIfacePhase) = IfacePublic {
- mi_exports_ :: [IfaceExport]
- mi_fixities_ :: [(OccName, Fixity)]
- mi_warns_ :: IfaceWarnings
- mi_anns_ :: [IfaceAnnotation]
- mi_decls_ :: [IfaceDeclExts phase]
- mi_defaults_ :: [IfaceDefault]
- mi_insts_ :: [IfaceClsInst]
- mi_fam_insts_ :: [IfaceFamInst]
- mi_rules_ :: [IfaceRule]
- mi_trust_ :: IfaceTrustInfo
- mi_trust_pkg_ :: Bool
- mi_complete_matches_ :: [IfaceCompleteMatch]
- mi_caches_ :: IfaceCache
- mi_abi_hashes_ :: IfaceAbiHashesExts phase
- type IfacePublic = IfacePublic_ 'ModIfaceFinal
- type PartialIfacePublic = IfacePublic_ 'ModIfaceCore
- data IfaceModInfo = IfaceModInfo {}
- 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_mod_info_semantic_module :: IfaceModInfo -> Module
- mi_free_holes :: ModIface -> UniqDSet ModuleName
- mi_mnwib :: ModIface -> ModuleNameWithIsBoot
- mi_flag_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags)
- mi_opt_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Fingerprint
- mi_hpc_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Fingerprint
- mi_plugin_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Fingerprint
- mi_src_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Fingerprint
- mi_usages :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe [Usage]
- mi_mod_hash :: ModIface -> Fingerprint
- mi_orphan :: ModIface -> WhetherHasOrphans
- mi_finsts :: ModIface -> WhetherHasFamInst
- mi_exp_hash :: ModIface -> Fingerprint
- mi_orphan_hash :: ModIface -> Fingerprint
- 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
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
Binary ModIface Source # | |
(NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (ModIface_ phase) Source # | |
Defined in GHC.Unit.Module.ModIface |
pattern ModIface :: IfaceModInfo -> Module -> Maybe Module -> HscSource -> Fingerprint -> Dependencies -> IfacePublic_ phase -> [IfaceExport] -> [(OccName, Fixity)] -> IfaceWarnings -> [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe IfaceSimplifiedCore -> [IfaceDefault] -> IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> IfaceAbiHashesExts phase -> ExtensibleFields -> IfaceBinHandle phase -> Maybe IfaceSelfRecomp -> (OccName -> Maybe Fixity) -> (OccName -> Maybe (OccName, Fingerprint)) -> (OccName -> Maybe (WarningTxt GhcRn)) -> (Name -> Maybe (WarningTxt GhcRn)) -> 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 #
completePartialModIface :: PartialModIface -> Fingerprint -> [(Fingerprint, IfaceDecl)] -> Maybe IfaceSimplifiedCore -> IfaceAbiHashes -> IfaceCache -> 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.
Constructors
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 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
|
Instances
NFData IfaceAbiHashes Source # | |
Defined in GHC.Unit.Module.ModIface Methods rnf :: IfaceAbiHashes -> () Source # | |
Binary IfaceAbiHashes Source # | |
Defined in GHC.Unit.Module.ModIface Methods put_ :: WriteBinHandle -> IfaceAbiHashes -> IO () Source # put :: WriteBinHandle -> IfaceAbiHashes -> IO (Bin IfaceAbiHashes) Source # get :: ReadBinHandle -> IO IfaceAbiHashes Source # |
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
|
Instances
NFData IfaceSelfRecomp Source # | |
Defined in GHC.Iface.Recomp.Types Methods rnf :: IfaceSelfRecomp -> () Source # | |
Binary IfaceSelfRecomp Source # | |
Defined in GHC.Iface.Recomp.Types Methods put_ :: WriteBinHandle -> IfaceSelfRecomp -> IO () Source # put :: WriteBinHandle -> IfaceSelfRecomp -> IO (Bin IfaceSelfRecomp) Source # get :: ReadBinHandle -> IO IfaceSelfRecomp Source # | |
Outputable IfaceSelfRecomp Source # | |
Defined in GHC.Iface.Recomp.Types Methods ppr :: IfaceSelfRecomp -> SDoc Source # |
data IfaceCache Source #
Constructors
IfaceCache | |
Fields
|
Instances
NFData IfaceCache Source # | |
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
|
Instances
NFData IfaceSimplifiedCore Source # | |
Defined in GHC.Unit.Module.ModIface Methods rnf :: IfaceSimplifiedCore -> () Source # | |
Binary IfaceSimplifiedCore Source # | |
Defined in GHC.Unit.Module.ModIface Methods put_ :: WriteBinHandle -> IfaceSimplifiedCore -> IO () Source # put :: WriteBinHandle -> IfaceSimplifiedCore -> IO (Bin IfaceSimplifiedCore) Source # get :: ReadBinHandle -> IO IfaceSimplifiedCore Source # |
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 |
type IfaceExport = AvailInfo Source #
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
(NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) Source # | |
Defined in GHC.Unit.Module.ModIface Methods rnf :: IfacePublic_ phase -> () Source # |
type IfacePublic = IfacePublic_ 'ModIfaceFinal Source #
type PartialIfacePublic = IfacePublic_ 'ModIfaceCore Source #
data IfaceModInfo Source #
Meta information about the module the interface file is for
Constructors
IfaceModInfo | |
Fields
|
Instances
NFData IfaceModInfo Source # | |
Defined in GHC.Unit.Module.ModIface Methods rnf :: IfaceModInfo -> () Source # | |
Binary IfaceModInfo Source # | |
Defined in GHC.Unit.Module.ModIface Methods put_ :: WriteBinHandle -> IfaceModInfo -> IO () Source # put :: WriteBinHandle -> IfaceModInfo -> IO (Bin IfaceModInfo) Source # get :: ReadBinHandle -> IO IfaceModInfo Source # |
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
NFData IfaceTopEnv Source # | |
Defined in GHC.Unit.Module.ModIface Methods rnf :: IfaceTopEnv -> () Source # | |
Binary IfaceTopEnv Source # | |
Defined in GHC.Unit.Module.ModIface Methods put_ :: WriteBinHandle -> IfaceTopEnv -> IO () Source # put :: WriteBinHandle -> IfaceTopEnv -> IO (Bin IfaceTopEnv) Source # get :: ReadBinHandle -> IO IfaceTopEnv Source # |
data IfaceImport Source #
Constructors
IfaceImport ImpDeclSpec ImpIfaceList |
Instances
NFData IfaceImport Source # | |
Defined in GHC.Iface.Syntax Methods rnf :: IfaceImport -> () Source # | |
Binary IfaceImport Source # | |
Defined in GHC.Iface.Syntax Methods put_ :: WriteBinHandle -> IfaceImport -> IO () Source # put :: WriteBinHandle -> IfaceImport -> IO (Bin IfaceImport) Source # get :: ReadBinHandle -> IO 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 #
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_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.
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 #