module GHC.Unit.Module.ModIface
( ModIface
, ModIface_ (..)
, PartialModIface
, ModIfaceBackend (..)
, IfaceDeclExts
, IfaceBackendExts
, IfaceExport
, WhetherHasOrphans
, WhetherHasFamInst
, mi_boot
, mi_fix
, mi_semantic_module
, mi_free_holes
, renameFreeHoles
, emptyPartialModIface
, emptyFullModIface
, mkIfaceHashCache
, emptyIfaceHashCache
)
where
import GHC.Prelude
import GHC.Hs
import GHC.Iface.Syntax
import GHC.Iface.Ext.Fields
import GHC.Unit
import GHC.Unit.Module.Deps
import GHC.Unit.Module.Warnings
import GHC.Types.Avail
import GHC.Types.Fixity
import GHC.Types.Fixity.Env
import GHC.Types.HpcInfo
import GHC.Types.Name
import GHC.Types.Name.Reader
import GHC.Types.SafeHaskell
import GHC.Types.SourceFile
import GHC.Types.Unique.DSet
import GHC.Types.Unique.FM
import GHC.Data.Maybe
import GHC.Utils.Fingerprint
import GHC.Utils.Binary
import Control.DeepSeq
type PartialModIface = ModIface_ 'ModIfaceCore
type ModIface = ModIface_ 'ModIfaceFinal
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)
, mi_fix_fn :: !(OccName -> Maybe Fixity)
, mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
}
data ModIfacePhase
= ModIfaceCore
| ModIfaceFinal
type family IfaceDeclExts (phase :: ModIfacePhase) where
IfaceDeclExts 'ModIfaceCore = IfaceDecl
IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl)
type family IfaceBackendExts (phase :: ModIfacePhase) where
IfaceBackendExts 'ModIfaceCore = ()
IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend
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,
mi_anns :: [IfaceAnnotation],
mi_decls :: [IfaceDeclExts phase],
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_doc_hdr :: Maybe HsDocString,
mi_decl_docs :: DeclDocMap,
mi_arg_docs :: ArgDocMap,
mi_final_exts :: !(IfaceBackendExts phase),
mi_ext_fields :: ExtensibleFields
}
mi_boot :: ModIface -> IsBootInterface
mi_boot iface = if mi_hsc_src iface == HsBootFile
then IsBoot
else NotBoot
mi_fix :: ModIface -> OccName -> Fixity
mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity
mi_semantic_module :: ModIface_ a -> Module
mi_semantic_module iface = case mi_sig_of iface of
Nothing -> mi_module iface
Just mod -> mod
mi_free_holes :: ModIface -> UniqDSet ModuleName
mi_free_holes iface =
case getModuleInstantiation (mi_module iface) of
(_, Just indef)
-> renameFreeHoles (mkUniqDSet cands) (instUnitInsts (moduleUnit indef))
_ -> emptyUniqDSet
where
cands = map gwib_mod $ dep_mods $ mi_deps iface
renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
renameFreeHoles fhs insts =
unionManyUniqDSets (map lookup_impl (uniqDSetToList fhs))
where
hmap = listToUFM insts
lookup_impl mod_name
| Just mod <- lookupUFM hmap mod_name = moduleFreeHoles mod
| otherwise = emptyUniqDSet
instance Binary ModIface where
put_ bh (ModIface {
mi_module = mod,
mi_sig_of = sig_of,
mi_hsc_src = hsc_src,
mi_deps = deps,
mi_usages = usages,
mi_exports = exports,
mi_used_th = used_th,
mi_fixities = fixities,
mi_warns = warns,
mi_anns = anns,
mi_decls = decls,
mi_insts = insts,
mi_fam_insts = fam_insts,
mi_rules = rules,
mi_hpc = hpc_info,
mi_trust = trust,
mi_trust_pkg = trust_pkg,
mi_complete_matches = complete_matches,
mi_doc_hdr = doc_hdr,
mi_decl_docs = decl_docs,
mi_arg_docs = arg_docs,
mi_ext_fields = _ext_fields,
mi_final_exts = ModIfaceBackend {
mi_iface_hash = iface_hash,
mi_mod_hash = mod_hash,
mi_flag_hash = flag_hash,
mi_opt_hash = opt_hash,
mi_hpc_hash = hpc_hash,
mi_plugin_hash = plugin_hash,
mi_orphan = orphan,
mi_finsts = hasFamInsts,
mi_exp_hash = exp_hash,
mi_orphan_hash = orphan_hash
}}) = do
put_ bh mod
put_ bh sig_of
put_ bh hsc_src
put_ bh iface_hash
put_ bh mod_hash
put_ bh flag_hash
put_ bh opt_hash
put_ bh hpc_hash
put_ bh plugin_hash
put_ bh orphan
put_ bh hasFamInsts
lazyPut bh deps
lazyPut bh usages
put_ bh exports
put_ bh exp_hash
put_ bh used_th
put_ bh fixities
lazyPut bh warns
lazyPut bh anns
put_ bh decls
put_ bh insts
put_ bh fam_insts
lazyPut bh rules
put_ bh orphan_hash
put_ bh hpc_info
put_ bh trust
put_ bh trust_pkg
put_ bh complete_matches
lazyPut bh doc_hdr
lazyPut bh decl_docs
lazyPut bh arg_docs
get bh = do
mod <- get bh
sig_of <- get bh
hsc_src <- get bh
iface_hash <- get bh
mod_hash <- get bh
flag_hash <- get bh
opt_hash <- get bh
hpc_hash <- get bh
plugin_hash <- get bh
orphan <- get bh
hasFamInsts <- get bh
deps <- lazyGet bh
usages <- lazyGet bh
exports <- get bh
exp_hash <- get bh
used_th <- get bh
fixities <- get bh
warns <- lazyGet bh
anns <- lazyGet bh
decls <- get bh
insts <- get bh
fam_insts <- get bh
rules <- lazyGet bh
orphan_hash <- get bh
hpc_info <- get bh
trust <- get bh
trust_pkg <- get bh
complete_matches <- get bh
doc_hdr <- lazyGet bh
decl_docs <- lazyGet bh
arg_docs <- lazyGet bh
return (ModIface {
mi_module = mod,
mi_sig_of = sig_of,
mi_hsc_src = hsc_src,
mi_deps = deps,
mi_usages = usages,
mi_exports = exports,
mi_used_th = used_th,
mi_anns = anns,
mi_fixities = fixities,
mi_warns = warns,
mi_decls = decls,
mi_globals = Nothing,
mi_insts = insts,
mi_fam_insts = fam_insts,
mi_rules = rules,
mi_hpc = hpc_info,
mi_trust = trust,
mi_trust_pkg = trust_pkg,
mi_complete_matches = complete_matches,
mi_doc_hdr = doc_hdr,
mi_decl_docs = decl_docs,
mi_arg_docs = arg_docs,
mi_ext_fields = emptyExtensibleFields,
mi_final_exts = ModIfaceBackend {
mi_iface_hash = iface_hash,
mi_mod_hash = mod_hash,
mi_flag_hash = flag_hash,
mi_opt_hash = opt_hash,
mi_hpc_hash = hpc_hash,
mi_plugin_hash = plugin_hash,
mi_orphan = orphan,
mi_finsts = hasFamInsts,
mi_exp_hash = exp_hash,
mi_orphan_hash = orphan_hash,
mi_warn_fn = mkIfaceWarnCache warns,
mi_fix_fn = mkIfaceFixCache fixities,
mi_hash_fn = mkIfaceHashCache decls
}})
type IfaceExport = AvailInfo
emptyPartialModIface :: Module -> PartialModIface
emptyPartialModIface mod
= ModIface { mi_module = mod,
mi_sig_of = Nothing,
mi_hsc_src = HsSrcFile,
mi_deps = noDependencies,
mi_usages = [],
mi_exports = [],
mi_used_th = False,
mi_fixities = [],
mi_warns = NoWarnings,
mi_anns = [],
mi_insts = [],
mi_fam_insts = [],
mi_rules = [],
mi_decls = [],
mi_globals = Nothing,
mi_hpc = False,
mi_trust = noIfaceTrustInfo,
mi_trust_pkg = False,
mi_complete_matches = [],
mi_doc_hdr = Nothing,
mi_decl_docs = emptyDeclDocMap,
mi_arg_docs = emptyArgDocMap,
mi_final_exts = (),
mi_ext_fields = emptyExtensibleFields
}
emptyFullModIface :: Module -> ModIface
emptyFullModIface mod =
(emptyPartialModIface mod)
{ mi_decls = []
, mi_final_exts = ModIfaceBackend
{ mi_iface_hash = fingerprint0,
mi_mod_hash = fingerprint0,
mi_flag_hash = fingerprint0,
mi_opt_hash = fingerprint0,
mi_hpc_hash = fingerprint0,
mi_plugin_hash = fingerprint0,
mi_orphan = False,
mi_finsts = False,
mi_exp_hash = fingerprint0,
mi_orphan_hash = fingerprint0,
mi_warn_fn = emptyIfaceWarnCache,
mi_fix_fn = emptyIfaceFixCache,
mi_hash_fn = emptyIfaceHashCache } }
mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
-> (OccName -> Maybe (OccName, Fingerprint))
mkIfaceHashCache pairs
= \occ -> lookupOccEnv env occ
where
env = foldl' add_decl emptyOccEnv pairs
add_decl env0 (v,d) = foldl' add env0 (ifaceDeclFingerprints v d)
where
add env0 (occ,hash) = extendOccEnv env0 occ (occ,hash)
emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
emptyIfaceHashCache _occ = Nothing
instance (NFData (IfaceBackendExts (phase :: ModIfacePhase)), NFData (IfaceDeclExts (phase :: ModIfacePhase))) => NFData (ModIface_ phase) where
rnf (ModIface f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 f12
f13 f14 f15 f16 f17 f18 f19 f20 f21 f22 f23 f24) =
rnf f1 `seq` rnf f2 `seq` f3 `seq` f4 `seq` f5 `seq` f6 `seq` rnf f7 `seq` f8 `seq`
f9 `seq` rnf f10 `seq` rnf f11 `seq` f12 `seq` rnf f13 `seq` rnf f14 `seq` rnf f15 `seq`
rnf f16 `seq` f17 `seq` rnf f18 `seq` rnf f19 `seq` f20 `seq` f21 `seq` f22 `seq` rnf f23
`seq` rnf f24
type WhetherHasOrphans = Bool
type WhetherHasFamInst = Bool