{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveAnyClass #-}
module GHC.Unit.Module.ModIface
( ModIface
, ModIface_
( mi_mod_info
, mi_module
, mi_sig_of
, mi_hsc_src
, mi_iface_hash
, mi_deps
, mi_public
, mi_exports
, mi_fixities
, mi_warns
, mi_anns
, mi_decls
, mi_defaults
, mi_simplified_core
, mi_top_env
, mi_insts
, mi_fam_insts
, mi_rules
, mi_trust
, mi_trust_pkg
, mi_complete_matches
, mi_docs
, mi_abi_hashes
, mi_ext_fields
, mi_hi_bytes
, mi_self_recomp_info
, mi_fix_fn
, mi_decl_warn_fn
, mi_export_warn_fn
, mi_hash_fn
)
, pattern ModIface
, set_mi_mod_info
, set_mi_module
, set_mi_sig_of
, set_mi_hsc_src
, set_mi_self_recomp
, set_mi_hi_bytes
, set_mi_deps
, set_mi_exports
, set_mi_fixities
, set_mi_warns
, set_mi_anns
, set_mi_insts
, set_mi_fam_insts
, set_mi_rules
, set_mi_decls
, set_mi_defaults
, set_mi_simplified_core
, set_mi_top_env
, set_mi_trust
, set_mi_trust_pkg
, set_mi_complete_matches
, set_mi_docs
, set_mi_abi_hashes
, set_mi_ext_fields
, set_mi_caches
, set_mi_decl_warn_fn
, set_mi_export_warn_fn
, set_mi_fix_fn
, set_mi_hash_fn
, completePartialModIface
, IfaceBinHandle(..)
, PartialModIface
, IfaceAbiHashes (..)
, IfaceSelfRecomp (..)
, IfaceCache (..)
, IfaceSimplifiedCore (..)
, withSelfRecomp
, IfaceDeclExts
, IfaceAbiHashesExts
, IfaceExport
, IfacePublic_(..)
, IfacePublic
, PartialIfacePublic
, IfaceModInfo(..)
, WhetherHasOrphans
, WhetherHasFamInst
, IfaceTopEnv (..)
, IfaceImport(..)
, mi_boot
, mi_fix
, mi_semantic_module
, mi_mod_info_semantic_module
, mi_free_holes
, mi_mnwib
, mi_flag_hash
, mi_opt_hash
, mi_hpc_hash
, mi_plugin_hash
, mi_src_hash
, mi_usages
, mi_mod_hash
, mi_orphan
, mi_finsts
, mi_exp_hash
, mi_orphan_hash
, renameFreeHoles
, emptyPartialModIface
, emptyFullModIface
, mkIfaceHashCache
, emptyIfaceHashCache
, forceModIface
)
where
import GHC.Prelude
import GHC.Hs
import GHC.Iface.Syntax
import GHC.Iface.Flags
import GHC.Iface.Ext.Fields
import GHC.Iface.Recomp.Types
import GHC.Unit
import GHC.Unit.Module.Deps
import GHC.Unit.Module.Warnings
import GHC.Unit.Module.WholeCoreBindings (IfaceForeign (..))
import GHC.Types.Avail
import GHC.Types.Fixity
import GHC.Types.Fixity.Env
import GHC.Types.Name
import GHC.Types.SafeHaskell
import GHC.Types.SourceFile
import GHC.Types.Unique.DSet
import GHC.Types.Unique.FM
import GHC.Data.Maybe
import qualified GHC.Data.Strict as Strict
import GHC.Utils.Fingerprint
import GHC.Utils.Binary
import Control.DeepSeq
import Control.Exception
type PartialModIface = ModIface_ 'ModIfaceCore
type ModIface = ModIface_ 'ModIfaceFinal
type PartialIfacePublic = IfacePublic_ 'ModIfaceCore
type IfacePublic = IfacePublic_ 'ModIfaceFinal
data IfaceAbiHashes = IfaceAbiHashes
{ IfaceAbiHashes -> Fingerprint
mi_abi_mod_hash :: !Fingerprint
, IfaceAbiHashes -> WhetherHasOrphans
mi_abi_orphan :: !WhetherHasOrphans
, IfaceAbiHashes -> WhetherHasOrphans
mi_abi_finsts :: !WhetherHasFamInst
, IfaceAbiHashes -> Fingerprint
mi_abi_exp_hash :: !Fingerprint
, IfaceAbiHashes -> Fingerprint
mi_abi_orphan_hash :: !Fingerprint
}
data IfaceCache = IfaceCache
{ IfaceCache -> OccName -> Maybe (WarningTxt GhcRn)
mi_cache_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn))
, IfaceCache -> Name -> Maybe (WarningTxt GhcRn)
mi_cache_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn))
, IfaceCache -> OccName -> Maybe Fixity
mi_cache_fix_fn :: !(OccName -> Maybe Fixity)
, IfaceCache -> OccName -> Maybe (OccName, Fingerprint)
mi_cache_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
}
data ModIfacePhase
= ModIfaceCore
| ModIfaceFinal
type family IfaceDeclExts (phase :: ModIfacePhase) = decl | decl -> phase where
IfaceDeclExts 'ModIfaceCore = IfaceDecl
IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl)
type family IfaceAbiHashesExts (phase :: ModIfacePhase) = bk | bk -> phase where
IfaceAbiHashesExts 'ModIfaceCore = ()
IfaceAbiHashesExts 'ModIfaceFinal = IfaceAbiHashes
data IfaceBinHandle (phase :: ModIfacePhase) where
PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore
FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal
withSelfRecomp :: ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r
withSelfRecomp :: forall (phase :: ModIfacePhase) r.
ModIface_ phase -> r -> (IfaceSelfRecomp -> r) -> r
withSelfRecomp ModIface_ phase
iface r
nk IfaceSelfRecomp -> r
jk =
case ModIface_ phase -> Maybe IfaceSelfRecomp
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_info ModIface_ phase
iface of
Maybe IfaceSelfRecomp
Nothing -> r
nk
Just IfaceSelfRecomp
x -> IfaceSelfRecomp -> r
jk IfaceSelfRecomp
x
data ModIface_ (phase :: ModIfacePhase)
= PrivateModIface {
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBinHandle phase
mi_hi_bytes_ :: !(IfaceBinHandle phase),
forall (phase :: ModIfacePhase). ModIface_ phase -> Fingerprint
mi_iface_hash_ :: Fingerprint,
forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceModInfo
mi_mod_info_ :: IfaceModInfo,
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps_ :: Dependencies,
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfacePublic_ phase
mi_public_ :: IfacePublic_ phase,
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_ :: Maybe IfaceSelfRecomp,
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSimplifiedCore
mi_simplified_core_ :: Maybe IfaceSimplifiedCore,
forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Docs
mi_docs_ :: Maybe Docs,
forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTopEnv
mi_top_env_ :: IfaceTopEnv,
forall (phase :: ModIfacePhase).
ModIface_ phase -> ExtensibleFields
mi_ext_fields_ :: ExtensibleFields
}
data IfaceModInfo = IfaceModInfo {
IfaceModInfo -> Module
mi_mod_info_module :: Module,
IfaceModInfo -> Maybe Module
mi_mod_info_sig_of :: Maybe Module,
IfaceModInfo -> HscSource
mi_mod_info_hsc_src :: HscSource
}
data IfacePublic_ phase = IfacePublic {
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceExport]
mi_exports_ :: [IfaceExport],
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [(OccName, Fixity)]
mi_fixities_ :: [(OccName,Fixity)],
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> IfaceWarnings
mi_warns_ :: IfaceWarnings,
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceAnnotation]
mi_anns_ :: [IfaceAnnotation],
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceDeclExts phase]
mi_decls_ :: [IfaceDeclExts phase],
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceDefault]
mi_defaults_ :: [IfaceDefault],
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceClsInst]
mi_insts_ :: [IfaceClsInst],
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceFamInst]
mi_fam_insts_ :: [IfaceFamInst],
forall (phase :: ModIfacePhase). IfacePublic_ phase -> [IfaceRule]
mi_rules_ :: [IfaceRule],
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> IfaceTrustInfo
mi_trust_ :: IfaceTrustInfo,
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> WhetherHasOrphans
mi_trust_pkg_ :: Bool,
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceCompleteMatch]
mi_complete_matches_ :: [IfaceCompleteMatch],
forall (phase :: ModIfacePhase). IfacePublic_ phase -> IfaceCache
mi_caches_ :: IfaceCache,
forall (phase :: ModIfacePhase).
IfacePublic_ phase -> IfaceAbiHashesExts phase
mi_abi_hashes_ :: (IfaceAbiHashesExts phase)
}
mkIfacePublic :: [IfaceExport]
-> [IfaceDeclExts 'ModIfaceFinal]
-> [(OccName, Fixity)]
-> IfaceWarnings
-> [IfaceAnnotation]
-> [IfaceDefault]
-> [IfaceClsInst]
-> [IfaceFamInst]
-> [IfaceRule]
-> IfaceTrustInfo
-> Bool
-> [IfaceCompleteMatch]
-> IfaceAbiHashes
-> IfacePublic
mkIfacePublic :: [IfaceExport]
-> [IfaceDeclExts 'ModIfaceFinal]
-> [(OccName, Fixity)]
-> IfaceWarnings
-> [IfaceAnnotation]
-> [IfaceDefault]
-> [IfaceClsInst]
-> [IfaceFamInst]
-> [IfaceRule]
-> IfaceTrustInfo
-> WhetherHasOrphans
-> [IfaceCompleteMatch]
-> IfaceAbiHashes
-> IfacePublic
mkIfacePublic [IfaceExport]
exports [IfaceDeclExts 'ModIfaceFinal]
decls [(OccName, Fixity)]
fixities IfaceWarnings
warns [IfaceAnnotation]
anns [IfaceDefault]
defaults [IfaceClsInst]
insts [IfaceFamInst]
fam_insts [IfaceRule]
rules IfaceTrustInfo
trust WhetherHasOrphans
trust_pkg [IfaceCompleteMatch]
complete_matches IfaceAbiHashes
abi_hashes = IfacePublic {
mi_exports_ :: [IfaceExport]
mi_exports_ = [IfaceExport]
exports,
mi_decls_ :: [IfaceDeclExts 'ModIfaceFinal]
mi_decls_ = [IfaceDeclExts 'ModIfaceFinal]
decls,
mi_fixities_ :: [(OccName, Fixity)]
mi_fixities_ = [(OccName, Fixity)]
fixities,
mi_warns_ :: IfaceWarnings
mi_warns_ = IfaceWarnings
warns,
mi_anns_ :: [IfaceAnnotation]
mi_anns_ = [IfaceAnnotation]
anns,
mi_defaults_ :: [IfaceDefault]
mi_defaults_ = [IfaceDefault]
defaults,
mi_insts_ :: [IfaceClsInst]
mi_insts_ = [IfaceClsInst]
insts,
mi_fam_insts_ :: [IfaceFamInst]
mi_fam_insts_ = [IfaceFamInst]
fam_insts,
mi_rules_ :: [IfaceRule]
mi_rules_ = [IfaceRule]
rules,
mi_trust_ :: IfaceTrustInfo
mi_trust_ = IfaceTrustInfo
trust,
mi_trust_pkg_ :: WhetherHasOrphans
mi_trust_pkg_ = WhetherHasOrphans
trust_pkg,
mi_complete_matches_ :: [IfaceCompleteMatch]
mi_complete_matches_ = [IfaceCompleteMatch]
complete_matches,
mi_caches_ :: IfaceCache
mi_caches_ = IfaceCache {
mi_cache_decl_warn_fn :: OccName -> Maybe (WarningTxt GhcRn)
mi_cache_decl_warn_fn = Warnings GhcRn -> OccName -> Maybe (WarningTxt GhcRn)
forall p. Warnings p -> OccName -> Maybe (WarningTxt p)
mkIfaceDeclWarnCache (Warnings GhcRn -> OccName -> Maybe (WarningTxt GhcRn))
-> Warnings GhcRn -> OccName -> Maybe (WarningTxt GhcRn)
forall a b. (a -> b) -> a -> b
$ IfaceWarnings -> Warnings GhcRn
fromIfaceWarnings IfaceWarnings
warns,
mi_cache_export_warn_fn :: Name -> Maybe (WarningTxt GhcRn)
mi_cache_export_warn_fn = Warnings GhcRn -> Name -> Maybe (WarningTxt GhcRn)
forall p. Warnings p -> Name -> Maybe (WarningTxt p)
mkIfaceExportWarnCache (Warnings GhcRn -> Name -> Maybe (WarningTxt GhcRn))
-> Warnings GhcRn -> Name -> Maybe (WarningTxt GhcRn)
forall a b. (a -> b) -> a -> b
$ IfaceWarnings -> Warnings GhcRn
fromIfaceWarnings IfaceWarnings
warns,
mi_cache_fix_fn :: OccName -> Maybe Fixity
mi_cache_fix_fn = [(OccName, Fixity)] -> OccName -> Maybe Fixity
mkIfaceFixCache [(OccName, Fixity)]
fixities,
mi_cache_hash_fn :: OccName -> Maybe (OccName, Fingerprint)
mi_cache_hash_fn = [(Fingerprint, IfaceDecl)]
-> OccName -> Maybe (OccName, Fingerprint)
mkIfaceHashCache [(Fingerprint, IfaceDecl)]
[IfaceDeclExts 'ModIfaceFinal]
decls
},
mi_abi_hashes_ :: IfaceAbiHashesExts 'ModIfaceFinal
mi_abi_hashes_ = IfaceAbiHashesExts 'ModIfaceFinal
IfaceAbiHashes
abi_hashes
}
data IfaceSimplifiedCore = IfaceSimplifiedCore {
:: [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
, IfaceSimplifiedCore -> IfaceForeign
mi_sc_foreign :: IfaceForeign
}
data IfaceTopEnv
= IfaceTopEnv
{ IfaceTopEnv -> DetOrdAvails
ifaceTopExports :: DetOrdAvails
, IfaceTopEnv -> [IfaceImport]
ifaceImports :: [IfaceImport]
}
instance NFData IfaceTopEnv where
rnf :: IfaceTopEnv -> ()
rnf (IfaceTopEnv DetOrdAvails
a [IfaceImport]
b) = DetOrdAvails -> ()
forall a. NFData a => a -> ()
rnf DetOrdAvails
a () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceImport] -> ()
forall a. NFData a => a -> ()
rnf [IfaceImport]
b
instance Binary IfaceTopEnv where
put_ :: WriteBinHandle -> IfaceTopEnv -> IO ()
put_ WriteBinHandle
bh (IfaceTopEnv DetOrdAvails
exports [IfaceImport]
imports) = do
WriteBinHandle -> DetOrdAvails -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh DetOrdAvails
exports
WriteBinHandle -> [IfaceImport] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceImport]
imports
get :: ReadBinHandle -> IO IfaceTopEnv
get ReadBinHandle
bh = do
exports <- ReadBinHandle -> IO DetOrdAvails
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
imports <- get bh
return (IfaceTopEnv exports imports)
mi_flag_hash :: ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags)
mi_flag_hash :: forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe (FingerprintWithValue IfaceDynFlags)
mi_flag_hash = (IfaceSelfRecomp -> FingerprintWithValue IfaceDynFlags)
-> Maybe IfaceSelfRecomp
-> Maybe (FingerprintWithValue IfaceDynFlags)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IfaceSelfRecomp -> FingerprintWithValue IfaceDynFlags
mi_sr_flag_hash (Maybe IfaceSelfRecomp
-> Maybe (FingerprintWithValue IfaceDynFlags))
-> (ModIface_ phase -> Maybe IfaceSelfRecomp)
-> ModIface_ phase
-> Maybe (FingerprintWithValue IfaceDynFlags)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface_ phase -> Maybe IfaceSelfRecomp
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_
mi_opt_hash :: ModIface_ phase -> Maybe Fingerprint
mi_opt_hash :: forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe Fingerprint
mi_opt_hash = (IfaceSelfRecomp -> Fingerprint)
-> Maybe IfaceSelfRecomp -> Maybe Fingerprint
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IfaceSelfRecomp -> Fingerprint
mi_sr_opt_hash (Maybe IfaceSelfRecomp -> Maybe Fingerprint)
-> (ModIface_ phase -> Maybe IfaceSelfRecomp)
-> ModIface_ phase
-> Maybe Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface_ phase -> Maybe IfaceSelfRecomp
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_
mi_hpc_hash :: ModIface_ phase -> Maybe Fingerprint
mi_hpc_hash :: forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe Fingerprint
mi_hpc_hash = (IfaceSelfRecomp -> Fingerprint)
-> Maybe IfaceSelfRecomp -> Maybe Fingerprint
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IfaceSelfRecomp -> Fingerprint
mi_sr_hpc_hash (Maybe IfaceSelfRecomp -> Maybe Fingerprint)
-> (ModIface_ phase -> Maybe IfaceSelfRecomp)
-> ModIface_ phase
-> Maybe Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface_ phase -> Maybe IfaceSelfRecomp
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_
mi_src_hash :: ModIface_ phase -> Maybe Fingerprint
mi_src_hash :: forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe Fingerprint
mi_src_hash = (IfaceSelfRecomp -> Fingerprint)
-> Maybe IfaceSelfRecomp -> Maybe Fingerprint
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IfaceSelfRecomp -> Fingerprint
mi_sr_src_hash (Maybe IfaceSelfRecomp -> Maybe Fingerprint)
-> (ModIface_ phase -> Maybe IfaceSelfRecomp)
-> ModIface_ phase
-> Maybe Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface_ phase -> Maybe IfaceSelfRecomp
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_
mi_usages :: ModIface_ phase -> Maybe [Usage]
mi_usages :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe [Usage]
mi_usages = (IfaceSelfRecomp -> [Usage])
-> Maybe IfaceSelfRecomp -> Maybe [Usage]
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IfaceSelfRecomp -> [Usage]
mi_sr_usages (Maybe IfaceSelfRecomp -> Maybe [Usage])
-> (ModIface_ phase -> Maybe IfaceSelfRecomp)
-> ModIface_ phase
-> Maybe [Usage]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface_ phase -> Maybe IfaceSelfRecomp
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_
mi_plugin_hash :: ModIface_ phase -> Maybe Fingerprint
mi_plugin_hash :: forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe Fingerprint
mi_plugin_hash = (IfaceSelfRecomp -> Fingerprint)
-> Maybe IfaceSelfRecomp -> Maybe Fingerprint
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IfaceSelfRecomp -> Fingerprint
mi_sr_plugin_hash (Maybe IfaceSelfRecomp -> Maybe Fingerprint)
-> (ModIface_ phase -> Maybe IfaceSelfRecomp)
-> ModIface_ phase
-> Maybe Fingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModIface_ phase -> Maybe IfaceSelfRecomp
forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_
mi_mod_hash :: ModIface -> Fingerprint
mi_mod_hash :: ModIface -> Fingerprint
mi_mod_hash ModIface
iface = IfaceAbiHashes -> Fingerprint
mi_abi_mod_hash (ModIface -> IfaceAbiHashesExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceAbiHashesExts phase
mi_abi_hashes ModIface
iface)
mi_orphan :: ModIface -> WhetherHasOrphans
mi_orphan :: ModIface -> WhetherHasOrphans
mi_orphan ModIface
iface = IfaceAbiHashes -> WhetherHasOrphans
mi_abi_orphan (ModIface -> IfaceAbiHashesExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceAbiHashesExts phase
mi_abi_hashes ModIface
iface)
mi_finsts :: ModIface -> WhetherHasFamInst
mi_finsts :: ModIface -> WhetherHasOrphans
mi_finsts ModIface
iface = IfaceAbiHashes -> WhetherHasOrphans
mi_abi_finsts (ModIface -> IfaceAbiHashesExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceAbiHashesExts phase
mi_abi_hashes ModIface
iface)
mi_exp_hash :: ModIface -> Fingerprint
mi_exp_hash :: ModIface -> Fingerprint
mi_exp_hash ModIface
iface = IfaceAbiHashes -> Fingerprint
mi_abi_exp_hash (ModIface -> IfaceAbiHashesExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceAbiHashesExts phase
mi_abi_hashes ModIface
iface)
mi_orphan_hash :: ModIface -> Fingerprint
mi_orphan_hash :: ModIface -> Fingerprint
mi_orphan_hash ModIface
iface = IfaceAbiHashes -> Fingerprint
mi_abi_orphan_hash (ModIface -> IfaceAbiHashesExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceAbiHashesExts phase
mi_abi_hashes ModIface
iface)
mi_boot :: ModIface -> IsBootInterface
mi_boot :: ModIface -> IsBootInterface
mi_boot ModIface
iface = if ModIface -> HscSource
forall (phase :: ModIfacePhase). ModIface_ phase -> HscSource
mi_hsc_src ModIface
iface HscSource -> HscSource -> WhetherHasOrphans
forall a. Eq a => a -> a -> WhetherHasOrphans
== HscSource
HsBootFile
then IsBootInterface
IsBoot
else IsBootInterface
NotBoot
mi_mnwib :: ModIface -> ModuleNameWithIsBoot
mi_mnwib :: ModIface -> ModuleNameWithIsBoot
mi_mnwib ModIface
iface = ModuleName -> IsBootInterface -> ModuleNameWithIsBoot
forall mod. mod -> IsBootInterface -> GenWithIsBoot mod
GWIB (Module -> ModuleName
forall unit. GenModule unit -> ModuleName
moduleName (Module -> ModuleName) -> Module -> ModuleName
forall a b. (a -> b) -> a -> b
$ ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface) (ModIface -> IsBootInterface
mi_boot ModIface
iface)
mi_fix :: ModIface -> OccName -> Fixity
mi_fix :: ModIface -> OccName -> Fixity
mi_fix ModIface
iface OccName
name = ModIface -> OccName -> Maybe Fixity
forall (phase :: ModIfacePhase).
ModIface_ phase -> OccName -> Maybe Fixity
mi_fix_fn ModIface
iface OccName
name Maybe Fixity -> Fixity -> Fixity
forall a. Maybe a -> a -> a
`orElse` Fixity
defaultFixity
mi_mod_info_semantic_module :: IfaceModInfo -> Module
mi_mod_info_semantic_module :: IfaceModInfo -> Module
mi_mod_info_semantic_module IfaceModInfo
iface = case IfaceModInfo -> Maybe Module
mi_mod_info_sig_of IfaceModInfo
iface of
Maybe Module
Nothing -> IfaceModInfo -> Module
mi_mod_info_module IfaceModInfo
iface
Just Module
mod -> Module
mod
mi_semantic_module :: ModIface_ a -> Module
mi_semantic_module :: forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_semantic_module ModIface_ a
iface = IfaceModInfo -> Module
mi_mod_info_semantic_module (ModIface_ a -> IfaceModInfo
forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceModInfo
mi_mod_info ModIface_ a
iface)
mi_free_holes :: ModIface -> UniqDSet ModuleName
mi_free_holes :: ModIface -> UniqDSet ModuleName
mi_free_holes ModIface
iface =
case Module -> (InstalledModule, Maybe InstantiatedModule)
getModuleInstantiation (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface) of
(InstalledModule
_, Just InstantiatedModule
indef)
-> UniqDSet ModuleName
-> [(ModuleName, Module)] -> UniqDSet ModuleName
renameFreeHoles ([ModuleName] -> UniqDSet ModuleName
forall a. Uniquable a => [a] -> UniqDSet a
mkUniqDSet [ModuleName]
cands) (GenInstantiatedUnit UnitId -> [(ModuleName, Module)]
forall unit. GenInstantiatedUnit unit -> GenInstantiations unit
instUnitInsts (InstantiatedModule -> GenInstantiatedUnit UnitId
forall unit. GenModule unit -> unit
moduleUnit InstantiatedModule
indef))
(InstalledModule, Maybe InstantiatedModule)
_ -> UniqDSet ModuleName
forall a. UniqDSet a
emptyUniqDSet
where
cands :: [ModuleName]
cands = Dependencies -> [ModuleName]
dep_sig_mods (Dependencies -> [ModuleName]) -> Dependencies -> [ModuleName]
forall a b. (a -> b) -> a -> b
$ ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface
renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
renameFreeHoles :: UniqDSet ModuleName
-> [(ModuleName, Module)] -> UniqDSet ModuleName
renameFreeHoles UniqDSet ModuleName
fhs [(ModuleName, Module)]
insts =
[UniqDSet ModuleName] -> UniqDSet ModuleName
forall a. [UniqDSet a] -> UniqDSet a
unionManyUniqDSets ((ModuleName -> UniqDSet ModuleName)
-> [ModuleName] -> [UniqDSet ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map ModuleName -> UniqDSet ModuleName
lookup_impl (UniqDSet ModuleName -> [ModuleName]
forall a. UniqDSet a -> [a]
uniqDSetToList UniqDSet ModuleName
fhs))
where
hmap :: UniqFM ModuleName Module
hmap = [(ModuleName, Module)] -> UniqFM ModuleName Module
forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM [(ModuleName, Module)]
insts
lookup_impl :: ModuleName -> UniqDSet ModuleName
lookup_impl ModuleName
mod_name
| Just Module
mod <- UniqFM ModuleName Module -> ModuleName -> Maybe Module
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM ModuleName Module
hmap ModuleName
mod_name = Module -> UniqDSet ModuleName
forall u. GenModule (GenUnit u) -> UniqDSet ModuleName
moduleFreeHoles Module
mod
| WhetherHasOrphans
otherwise = UniqDSet ModuleName
forall a. UniqDSet a
emptyUniqDSet
instance Binary ModIface where
put_ :: WriteBinHandle -> ModIface -> IO ()
put_ WriteBinHandle
bh (PrivateModIface
{ mi_hi_bytes_ :: forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBinHandle phase
mi_hi_bytes_ = IfaceBinHandle 'ModIfaceFinal
_hi_bytes,
mi_mod_info_ :: forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceModInfo
mi_mod_info_ = IfaceModInfo
mod_info,
mi_iface_hash_ :: forall (phase :: ModIfacePhase). ModIface_ phase -> Fingerprint
mi_iface_hash_ = Fingerprint
iface_hash,
mi_deps_ :: forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps_ = Dependencies
deps,
mi_public_ :: forall (phase :: ModIfacePhase).
ModIface_ phase -> IfacePublic_ phase
mi_public_ = IfacePublic
public,
mi_top_env_ :: forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTopEnv
mi_top_env_ = IfaceTopEnv
top_env,
mi_docs_ :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Docs
mi_docs_ = Maybe Docs
docs,
mi_ext_fields_ :: forall (phase :: ModIfacePhase).
ModIface_ phase -> ExtensibleFields
mi_ext_fields_ = ExtensibleFields
_ext_fields,
mi_self_recomp_ :: forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_ = Maybe IfaceSelfRecomp
self_recomp,
mi_simplified_core_ :: forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSimplifiedCore
mi_simplified_core_ = Maybe IfaceSimplifiedCore
simplified_core
}) = do
WriteBinHandle -> IfaceModInfo -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceModInfo
mod_info
WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Fingerprint
iface_hash
WriteBinHandle -> Dependencies -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh Dependencies
deps
WriteBinHandle -> IfacePublic -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh IfacePublic
public
WriteBinHandle -> IfaceTopEnv -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh IfaceTopEnv
top_env
WriteBinHandle -> Maybe Docs -> IO ()
forall a. Binary a => WriteBinHandle -> Maybe a -> IO ()
lazyPutMaybe WriteBinHandle
bh Maybe Docs
docs
WriteBinHandle -> Maybe IfaceSelfRecomp -> IO ()
forall a. Binary a => WriteBinHandle -> Maybe a -> IO ()
lazyPutMaybe WriteBinHandle
bh Maybe IfaceSelfRecomp
self_recomp
WriteBinHandle -> Maybe IfaceSimplifiedCore -> IO ()
forall a. Binary a => WriteBinHandle -> Maybe a -> IO ()
lazyPutMaybe WriteBinHandle
bh Maybe IfaceSimplifiedCore
simplified_core
get :: ReadBinHandle -> IO ModIface
get ReadBinHandle
bh = do
mod_info <- ReadBinHandle -> IO IfaceModInfo
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
iface_hash <- get bh
deps <- lazyGet bh
public <- lazyGet bh
top_env <- lazyGet bh
docs <- lazyGetMaybe bh
self_recomp <- lazyGetMaybe bh
simplified_core <- lazyGetMaybe bh
return (PrivateModIface {
mi_mod_info_ = mod_info,
mi_iface_hash_ = iface_hash,
mi_deps_ = deps,
mi_public_ = public,
mi_simplified_core_ = simplified_core,
mi_docs_ = docs,
mi_top_env_ = top_env,
mi_self_recomp_ = self_recomp,
mi_ext_fields_ = emptyExtensibleFields,
mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing
})
instance Binary IfaceModInfo where
put_ :: WriteBinHandle -> IfaceModInfo -> IO ()
put_ WriteBinHandle
bh (IfaceModInfo { mi_mod_info_module :: IfaceModInfo -> Module
mi_mod_info_module = Module
mod
, mi_mod_info_sig_of :: IfaceModInfo -> Maybe Module
mi_mod_info_sig_of = Maybe Module
sig_of
, mi_mod_info_hsc_src :: IfaceModInfo -> HscSource
mi_mod_info_hsc_src = HscSource
hsc_src
}) = do
WriteBinHandle -> Module -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Module
mod
WriteBinHandle -> Maybe Module -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Maybe Module
sig_of
WriteBinHandle -> HscSource -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh HscSource
hsc_src
get :: ReadBinHandle -> IO IfaceModInfo
get ReadBinHandle
bh = do
mod <- ReadBinHandle -> IO Module
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
sig_of <- get bh
hsc_src <- get bh
return (IfaceModInfo { mi_mod_info_module = mod
, mi_mod_info_sig_of = sig_of
, mi_mod_info_hsc_src = hsc_src
})
instance Binary (IfacePublic_ 'ModIfaceFinal) where
put_ :: WriteBinHandle -> IfacePublic -> IO ()
put_ WriteBinHandle
bh (IfacePublic { mi_exports_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceExport]
mi_exports_ = [IfaceExport]
exports
, mi_decls_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceDeclExts phase]
mi_decls_ = [IfaceDeclExts 'ModIfaceFinal]
decls
, mi_fixities_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [(OccName, Fixity)]
mi_fixities_ = [(OccName, Fixity)]
fixities
, mi_warns_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> IfaceWarnings
mi_warns_ = IfaceWarnings
warns
, mi_anns_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceAnnotation]
mi_anns_ = [IfaceAnnotation]
anns
, mi_defaults_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceDefault]
mi_defaults_ = [IfaceDefault]
defaults
, mi_insts_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceClsInst]
mi_insts_ = [IfaceClsInst]
insts
, mi_fam_insts_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceFamInst]
mi_fam_insts_ = [IfaceFamInst]
fam_insts
, mi_rules_ :: forall (phase :: ModIfacePhase). IfacePublic_ phase -> [IfaceRule]
mi_rules_ = [IfaceRule]
rules
, mi_trust_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> IfaceTrustInfo
mi_trust_ = IfaceTrustInfo
trust
, mi_trust_pkg_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> WhetherHasOrphans
mi_trust_pkg_ = WhetherHasOrphans
trust_pkg
, mi_complete_matches_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> [IfaceCompleteMatch]
mi_complete_matches_ = [IfaceCompleteMatch]
complete_matches
, mi_abi_hashes_ :: forall (phase :: ModIfacePhase).
IfacePublic_ phase -> IfaceAbiHashesExts phase
mi_abi_hashes_ = IfaceAbiHashesExts 'ModIfaceFinal
abi_hashes
}) = do
WriteBinHandle -> [IfaceExport] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh [IfaceExport]
exports
WriteBinHandle -> [(Fingerprint, IfaceDecl)] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh [(Fingerprint, IfaceDecl)]
[IfaceDeclExts 'ModIfaceFinal]
decls
WriteBinHandle -> [(OccName, Fixity)] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh [(OccName, Fixity)]
fixities
WriteBinHandle -> IfaceWarnings -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh IfaceWarnings
warns
WriteBinHandle -> [IfaceAnnotation] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh [IfaceAnnotation]
anns
WriteBinHandle -> [IfaceDefault] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh [IfaceDefault]
defaults
WriteBinHandle -> [IfaceClsInst] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh [IfaceClsInst]
insts
WriteBinHandle -> [IfaceFamInst] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh [IfaceFamInst]
fam_insts
WriteBinHandle -> [IfaceRule] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh [IfaceRule]
rules
WriteBinHandle -> IfaceTrustInfo -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh IfaceTrustInfo
trust
WriteBinHandle -> WhetherHasOrphans -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh WhetherHasOrphans
trust_pkg
WriteBinHandle -> [IfaceCompleteMatch] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh [IfaceCompleteMatch]
complete_matches
WriteBinHandle -> IfaceAbiHashes -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
lazyPut WriteBinHandle
bh IfaceAbiHashesExts 'ModIfaceFinal
IfaceAbiHashes
abi_hashes
get :: ReadBinHandle -> IO IfacePublic
get ReadBinHandle
bh = do
exports <- ReadBinHandle -> IO [IfaceExport]
forall a. Binary a => ReadBinHandle -> IO a
lazyGet ReadBinHandle
bh
decls <- lazyGet bh
fixities <- lazyGet bh
warns <- lazyGet bh
anns <- lazyGet bh
defaults <- lazyGet bh
insts <- lazyGet bh
fam_insts <- lazyGet bh
rules <- lazyGet bh
trust <- lazyGet bh
trust_pkg <- lazyGet bh
complete_matches <- lazyGet bh
abi_hashes <- lazyGet bh
return (mkIfacePublic exports decls fixities warns anns defaults insts fam_insts rules trust trust_pkg complete_matches abi_hashes)
instance Binary IfaceAbiHashes where
put_ :: WriteBinHandle -> IfaceAbiHashes -> IO ()
put_ WriteBinHandle
bh (IfaceAbiHashes { mi_abi_mod_hash :: IfaceAbiHashes -> Fingerprint
mi_abi_mod_hash = Fingerprint
mod_hash
, mi_abi_orphan :: IfaceAbiHashes -> WhetherHasOrphans
mi_abi_orphan = WhetherHasOrphans
orphan
, mi_abi_finsts :: IfaceAbiHashes -> WhetherHasOrphans
mi_abi_finsts = WhetherHasOrphans
hasFamInsts
, mi_abi_exp_hash :: IfaceAbiHashes -> Fingerprint
mi_abi_exp_hash = Fingerprint
exp_hash
, mi_abi_orphan_hash :: IfaceAbiHashes -> Fingerprint
mi_abi_orphan_hash = Fingerprint
orphan_hash
}) = do
WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Fingerprint
mod_hash
WriteBinHandle -> WhetherHasOrphans -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh WhetherHasOrphans
orphan
WriteBinHandle -> WhetherHasOrphans -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh WhetherHasOrphans
hasFamInsts
WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Fingerprint
exp_hash
WriteBinHandle -> Fingerprint -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh Fingerprint
orphan_hash
get :: ReadBinHandle -> IO IfaceAbiHashes
get ReadBinHandle
bh = do
mod_hash <- ReadBinHandle -> IO Fingerprint
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
orphan <- get bh
hasFamInsts <- get bh
exp_hash <- get bh
orphan_hash <- get bh
return $ IfaceAbiHashes {
mi_abi_mod_hash = mod_hash,
mi_abi_orphan = orphan,
mi_abi_finsts = hasFamInsts,
mi_abi_exp_hash = exp_hash,
mi_abi_orphan_hash = orphan_hash
}
instance Binary IfaceSimplifiedCore where
put_ :: WriteBinHandle -> IfaceSimplifiedCore -> IO ()
put_ WriteBinHandle
bh (IfaceSimplifiedCore [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
eds IfaceForeign
fs) = do
WriteBinHandle
-> [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
eds
WriteBinHandle -> IfaceForeign -> IO ()
forall a. Binary a => WriteBinHandle -> a -> IO ()
put_ WriteBinHandle
bh IfaceForeign
fs
get :: ReadBinHandle -> IO IfaceSimplifiedCore
get ReadBinHandle
bh = do
eds <- ReadBinHandle -> IO [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
forall a. Binary a => ReadBinHandle -> IO a
get ReadBinHandle
bh
fs <- get bh
return (IfaceSimplifiedCore eds fs)
emptyPartialModIface :: Module -> PartialModIface
emptyPartialModIface :: Module -> PartialModIface
emptyPartialModIface Module
mod
= PrivateModIface
{ mi_mod_info_ :: IfaceModInfo
mi_mod_info_ = Module -> IfaceModInfo
emptyIfaceModInfo Module
mod,
mi_iface_hash_ :: Fingerprint
mi_iface_hash_ = Fingerprint
fingerprint0,
mi_hi_bytes_ :: IfaceBinHandle 'ModIfaceCore
mi_hi_bytes_ = IfaceBinHandle 'ModIfaceCore
PartialIfaceBinHandle,
mi_deps_ :: Dependencies
mi_deps_ = Dependencies
noDependencies,
mi_public_ :: IfacePublic_ 'ModIfaceCore
mi_public_ = IfaceAbiHashesExts 'ModIfaceCore -> IfacePublic_ 'ModIfaceCore
forall (phase :: ModIfacePhase).
IfaceAbiHashesExts phase -> IfacePublic_ phase
emptyPublicModIface (),
mi_simplified_core_ :: Maybe IfaceSimplifiedCore
mi_simplified_core_ = Maybe IfaceSimplifiedCore
forall a. Maybe a
Nothing,
mi_top_env_ :: IfaceTopEnv
mi_top_env_ = DetOrdAvails -> [IfaceImport] -> IfaceTopEnv
IfaceTopEnv DetOrdAvails
emptyDetOrdAvails [] ,
mi_docs_ :: Maybe Docs
mi_docs_ = Maybe Docs
forall a. Maybe a
Nothing,
mi_self_recomp_ :: Maybe IfaceSelfRecomp
mi_self_recomp_ = Maybe IfaceSelfRecomp
forall a. Maybe a
Nothing,
mi_ext_fields_ :: ExtensibleFields
mi_ext_fields_ = ExtensibleFields
emptyExtensibleFields
}
emptyIfaceModInfo :: Module -> IfaceModInfo
emptyIfaceModInfo :: Module -> IfaceModInfo
emptyIfaceModInfo Module
mod = IfaceModInfo
{ mi_mod_info_module :: Module
mi_mod_info_module = Module
mod
, mi_mod_info_sig_of :: Maybe Module
mi_mod_info_sig_of = Maybe Module
forall a. Maybe a
Nothing
, mi_mod_info_hsc_src :: HscSource
mi_mod_info_hsc_src = HscSource
HsSrcFile
}
emptyPublicModIface :: IfaceAbiHashesExts phase -> IfacePublic_ phase
emptyPublicModIface :: forall (phase :: ModIfacePhase).
IfaceAbiHashesExts phase -> IfacePublic_ phase
emptyPublicModIface IfaceAbiHashesExts phase
abi_hashes = IfacePublic
{ mi_exports_ :: [IfaceExport]
mi_exports_ = []
, mi_decls_ :: [IfaceDeclExts phase]
mi_decls_ = []
, mi_fixities_ :: [(OccName, Fixity)]
mi_fixities_ = []
, mi_warns_ :: IfaceWarnings
mi_warns_ = [(OccName, IfaceWarningTxt)]
-> [(Name, IfaceWarningTxt)] -> IfaceWarnings
IfWarnSome [] []
, mi_anns_ :: [IfaceAnnotation]
mi_anns_ = []
, mi_defaults_ :: [IfaceDefault]
mi_defaults_ = []
, mi_insts_ :: [IfaceClsInst]
mi_insts_ = []
, mi_fam_insts_ :: [IfaceFamInst]
mi_fam_insts_ = []
, mi_rules_ :: [IfaceRule]
mi_rules_ = []
, mi_abi_hashes_ :: IfaceAbiHashesExts phase
mi_abi_hashes_ = IfaceAbiHashesExts phase
abi_hashes
, mi_trust_ :: IfaceTrustInfo
mi_trust_ = IfaceTrustInfo
noIfaceTrustInfo
, mi_trust_pkg_ :: WhetherHasOrphans
mi_trust_pkg_ = WhetherHasOrphans
False
, mi_caches_ :: IfaceCache
mi_caches_ = IfaceCache
emptyModIfaceCache
, mi_complete_matches_ :: [IfaceCompleteMatch]
mi_complete_matches_ = []
}
emptyModIfaceCache :: IfaceCache
emptyModIfaceCache :: IfaceCache
emptyModIfaceCache = IfaceCache {
mi_cache_decl_warn_fn :: OccName -> Maybe (WarningTxt GhcRn)
mi_cache_decl_warn_fn = OccName -> Maybe (WarningTxt GhcRn)
forall name p. name -> Maybe (WarningTxt p)
emptyIfaceWarnCache,
mi_cache_export_warn_fn :: Name -> Maybe (WarningTxt GhcRn)
mi_cache_export_warn_fn = Name -> Maybe (WarningTxt GhcRn)
forall name p. name -> Maybe (WarningTxt p)
emptyIfaceWarnCache,
mi_cache_fix_fn :: OccName -> Maybe Fixity
mi_cache_fix_fn = OccName -> Maybe Fixity
emptyIfaceFixCache,
mi_cache_hash_fn :: OccName -> Maybe (OccName, Fingerprint)
mi_cache_hash_fn = OccName -> Maybe (OccName, Fingerprint)
emptyIfaceHashCache
}
emptyIfaceBackend :: IfaceAbiHashes
emptyIfaceBackend :: IfaceAbiHashes
emptyIfaceBackend = IfaceAbiHashes
{ mi_abi_mod_hash :: Fingerprint
mi_abi_mod_hash = Fingerprint
fingerprint0,
mi_abi_orphan :: WhetherHasOrphans
mi_abi_orphan = WhetherHasOrphans
False,
mi_abi_finsts :: WhetherHasOrphans
mi_abi_finsts = WhetherHasOrphans
False,
mi_abi_exp_hash :: Fingerprint
mi_abi_exp_hash = Fingerprint
fingerprint0,
mi_abi_orphan_hash :: Fingerprint
mi_abi_orphan_hash = Fingerprint
fingerprint0
}
emptyFullModIface :: Module -> ModIface
emptyFullModIface :: Module -> ModIface
emptyFullModIface Module
mod =
(Module -> PartialModIface
emptyPartialModIface Module
mod)
{ mi_public_ = emptyPublicModIface emptyIfaceBackend
, mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing
}
mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
-> (OccName -> Maybe (OccName, Fingerprint))
mkIfaceHashCache :: [(Fingerprint, IfaceDecl)]
-> OccName -> Maybe (OccName, Fingerprint)
mkIfaceHashCache [(Fingerprint, IfaceDecl)]
pairs
= \OccName
occ -> OccEnv (OccName, Fingerprint)
-> OccName -> Maybe (OccName, Fingerprint)
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv (OccName, Fingerprint)
env OccName
occ
where
env :: OccEnv (OccName, Fingerprint)
env = (OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> OccEnv (OccName, Fingerprint))
-> OccEnv (OccName, Fingerprint)
-> [(Fingerprint, IfaceDecl)]
-> OccEnv (OccName, Fingerprint)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> OccEnv (OccName, Fingerprint)
add_decl OccEnv (OccName, Fingerprint)
forall a. OccEnv a
emptyOccEnv [(Fingerprint, IfaceDecl)]
pairs
add_decl :: OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> OccEnv (OccName, Fingerprint)
add_decl OccEnv (OccName, Fingerprint)
env0 (Fingerprint
v,IfaceDecl
d) = (OccEnv (OccName, Fingerprint)
-> (OccName, Fingerprint) -> OccEnv (OccName, Fingerprint))
-> OccEnv (OccName, Fingerprint)
-> [(OccName, Fingerprint)]
-> OccEnv (OccName, Fingerprint)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' OccEnv (OccName, Fingerprint)
-> (OccName, Fingerprint) -> OccEnv (OccName, Fingerprint)
forall {b}.
OccEnv (OccName, b) -> (OccName, b) -> OccEnv (OccName, b)
add OccEnv (OccName, Fingerprint)
env0 (Fingerprint -> IfaceDecl -> [(OccName, Fingerprint)]
ifaceDeclFingerprints Fingerprint
v IfaceDecl
d)
where
add :: OccEnv (OccName, b) -> (OccName, b) -> OccEnv (OccName, b)
add OccEnv (OccName, b)
env0 (OccName
occ,b
hash) = OccEnv (OccName, b)
-> OccName -> (OccName, b) -> OccEnv (OccName, b)
forall a. OccEnv a -> OccName -> a -> OccEnv a
extendOccEnv OccEnv (OccName, b)
env0 OccName
occ (OccName
occ,b
hash)
emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
emptyIfaceHashCache OccName
_occ = Maybe (OccName, Fingerprint)
forall a. Maybe a
Nothing
instance ( NFData (IfaceAbiHashesExts (phase :: ModIfacePhase))
, NFData (IfaceDeclExts (phase :: ModIfacePhase))
) => NFData (ModIface_ phase) where
rnf :: ModIface_ phase -> ()
rnf (PrivateModIface IfaceBinHandle phase
a1 Fingerprint
a2 IfaceModInfo
a3 Dependencies
a4 IfacePublic_ phase
a5 Maybe IfaceSelfRecomp
a6 Maybe IfaceSimplifiedCore
a7 Maybe Docs
a8 IfaceTopEnv
a9 ExtensibleFields
a10)
= (IfaceBinHandle phase
a1 :: IfaceBinHandle phase)
IfaceBinHandle phase -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
a2
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceModInfo -> ()
forall a. NFData a => a -> ()
rnf IfaceModInfo
a3
() -> () -> ()
forall a b. a -> b -> b
`seq` Dependencies -> ()
forall a. NFData a => a -> ()
rnf Dependencies
a4
() -> () -> ()
forall a b. a -> b -> b
`seq` IfacePublic_ phase -> ()
forall a. NFData a => a -> ()
rnf IfacePublic_ phase
a5
() -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfaceSelfRecomp -> ()
forall a. NFData a => a -> ()
rnf Maybe IfaceSelfRecomp
a6
() -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfaceSimplifiedCore -> ()
forall a. NFData a => a -> ()
rnf Maybe IfaceSimplifiedCore
a7
() -> () -> ()
forall a b. a -> b -> b
`seq` Maybe Docs -> ()
forall a. NFData a => a -> ()
rnf Maybe Docs
a8
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceTopEnv -> ()
forall a. NFData a => a -> ()
rnf IfaceTopEnv
a9
() -> () -> ()
forall a b. a -> b -> b
`seq` ExtensibleFields -> ()
forall a. NFData a => a -> ()
rnf ExtensibleFields
a10
instance NFData IfaceModInfo where
rnf :: IfaceModInfo -> ()
rnf (IfaceModInfo Module
a1 Maybe Module
a2 HscSource
a3)
= Module -> ()
forall a. NFData a => a -> ()
rnf Module
a1
() -> () -> ()
forall a b. a -> b -> b
`seq` Maybe Module -> ()
forall a. NFData a => a -> ()
rnf Maybe Module
a2
() -> () -> ()
forall a b. a -> b -> b
`seq` HscSource -> ()
forall a. NFData a => a -> ()
rnf HscSource
a3
instance NFData IfaceSimplifiedCore where
rnf :: IfaceSimplifiedCore -> ()
rnf (IfaceSimplifiedCore [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
eds IfaceForeign
fs) = [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ()
forall a. NFData a => a -> ()
rnf [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
eds () -> () -> ()
forall a b. a -> b -> b
`seq` IfaceForeign -> ()
forall a. NFData a => a -> ()
rnf IfaceForeign
fs
instance NFData IfaceAbiHashes where
rnf :: IfaceAbiHashes -> ()
rnf (IfaceAbiHashes Fingerprint
a1 WhetherHasOrphans
a2 WhetherHasOrphans
a3 Fingerprint
a4 Fingerprint
a5)
= Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
a1
() -> () -> ()
forall a b. a -> b -> b
`seq` WhetherHasOrphans -> ()
forall a. NFData a => a -> ()
rnf WhetherHasOrphans
a2
() -> () -> ()
forall a b. a -> b -> b
`seq` WhetherHasOrphans -> ()
forall a. NFData a => a -> ()
rnf WhetherHasOrphans
a3
() -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
a4
() -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
a5
instance (NFData (IfaceAbiHashesExts phase), NFData (IfaceDeclExts phase)) => NFData (IfacePublic_ phase) where
rnf :: IfacePublic_ phase -> ()
rnf (IfacePublic [IfaceExport]
a1 [(OccName, Fixity)]
a2 IfaceWarnings
a3 [IfaceAnnotation]
a4 [IfaceDeclExts phase]
a5 [IfaceDefault]
a6 [IfaceClsInst]
a7 [IfaceFamInst]
a8 [IfaceRule]
a9 IfaceTrustInfo
a10 WhetherHasOrphans
a11 [IfaceCompleteMatch]
a12 IfaceCache
a13 IfaceAbiHashesExts phase
a14)
= [IfaceExport] -> ()
forall a. NFData a => a -> ()
rnf [IfaceExport]
a1
() -> () -> ()
forall a b. a -> b -> b
`seq` [(OccName, Fixity)] -> ()
forall a. NFData a => a -> ()
rnf [(OccName, Fixity)]
a2
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceWarnings -> ()
forall a. NFData a => a -> ()
rnf IfaceWarnings
a3
() -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceAnnotation] -> ()
forall a. NFData a => a -> ()
rnf [IfaceAnnotation]
a4
() -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceDeclExts phase] -> ()
forall a. NFData a => a -> ()
rnf [IfaceDeclExts phase]
a5
() -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceDefault] -> ()
forall a. NFData a => a -> ()
rnf [IfaceDefault]
a6
() -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceClsInst] -> ()
forall a. NFData a => a -> ()
rnf [IfaceClsInst]
a7
() -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceFamInst] -> ()
forall a. NFData a => a -> ()
rnf [IfaceFamInst]
a8
() -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceRule] -> ()
forall a. NFData a => a -> ()
rnf [IfaceRule]
a9
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceTrustInfo -> ()
forall a. NFData a => a -> ()
rnf IfaceTrustInfo
a10
() -> () -> ()
forall a b. a -> b -> b
`seq` WhetherHasOrphans -> ()
forall a. NFData a => a -> ()
rnf WhetherHasOrphans
a11
() -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceCompleteMatch] -> ()
forall a. NFData a => a -> ()
rnf [IfaceCompleteMatch]
a12
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceCache -> ()
forall a. NFData a => a -> ()
rnf IfaceCache
a13
() -> () -> ()
forall a b. a -> b -> b
`seq` IfaceAbiHashesExts phase -> ()
forall a. NFData a => a -> ()
rnf IfaceAbiHashesExts phase
a14
instance NFData IfaceCache where
rnf :: IfaceCache -> ()
rnf (IfaceCache OccName -> Maybe (WarningTxt GhcRn)
a1 Name -> Maybe (WarningTxt GhcRn)
a2 OccName -> Maybe Fixity
a3 OccName -> Maybe (OccName, Fingerprint)
a4)
= (OccName -> Maybe (WarningTxt GhcRn)) -> ()
forall a. NFData a => a -> ()
rnf OccName -> Maybe (WarningTxt GhcRn)
a1
() -> () -> ()
forall a b. a -> b -> b
`seq` (Name -> Maybe (WarningTxt GhcRn)) -> ()
forall a. NFData a => a -> ()
rnf Name -> Maybe (WarningTxt GhcRn)
a2
() -> () -> ()
forall a b. a -> b -> b
`seq` (OccName -> Maybe Fixity) -> ()
forall a. NFData a => a -> ()
rnf OccName -> Maybe Fixity
a3
() -> () -> ()
forall a b. a -> b -> b
`seq` (OccName -> Maybe (OccName, Fingerprint)) -> ()
forall a. NFData a => a -> ()
rnf OccName -> Maybe (OccName, Fingerprint)
a4
forceModIface :: ModIface -> IO ()
forceModIface :: ModIface -> IO ()
forceModIface ModIface
iface = () () -> IO ModIface -> IO ()
forall a b. a -> IO b -> IO a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ModIface -> IO ModIface
forall a. a -> IO a
evaluate (ModIface -> IO ModIface) -> ModIface -> IO ModIface
forall a b. (a -> b) -> a -> b
$ ModIface -> ModIface
forall a. NFData a => a -> a
force ModIface
iface)
type WhetherHasOrphans = Bool
type WhetherHasFamInst = Bool
completePartialModIface :: PartialModIface
-> Fingerprint
-> [(Fingerprint, IfaceDecl)]
-> Maybe IfaceSimplifiedCore
-> IfaceAbiHashes
-> IfaceCache
-> ModIface
completePartialModIface :: PartialModIface
-> Fingerprint
-> [(Fingerprint, IfaceDecl)]
-> Maybe IfaceSimplifiedCore
-> IfaceAbiHashes
-> IfaceCache
-> ModIface
completePartialModIface PartialModIface
partial Fingerprint
iface_hash [(Fingerprint, IfaceDecl)]
decls Maybe IfaceSimplifiedCore
extra_decls IfaceAbiHashes
final_exts IfaceCache
cache = PartialModIface
partial
{ mi_public_ = completePublicModIface decls final_exts cache (mi_public_ partial)
, mi_simplified_core_ = extra_decls
, mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing
, mi_iface_hash_ = iface_hash
}
where
completePublicModIface :: [(Fingerprint, IfaceDecl)]
-> IfaceAbiHashes
-> IfaceCache
-> PartialIfacePublic
-> IfacePublic
completePublicModIface :: [(Fingerprint, IfaceDecl)]
-> IfaceAbiHashes
-> IfaceCache
-> IfacePublic_ 'ModIfaceCore
-> IfacePublic
completePublicModIface [(Fingerprint, IfaceDecl)]
decls IfaceAbiHashes
abi_hashes IfaceCache
cache IfacePublic_ 'ModIfaceCore
partial = IfacePublic_ 'ModIfaceCore
partial
{ mi_decls_ = decls
, mi_abi_hashes_ = abi_hashes
, mi_caches_ = cache
}
set_mi_mod_info :: IfaceModInfo -> ModIface_ phase -> ModIface_ phase
set_mi_mod_info :: forall (phase :: ModIfacePhase).
IfaceModInfo -> ModIface_ phase -> ModIface_ phase
set_mi_mod_info IfaceModInfo
val ModIface_ phase
iface = ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes (ModIface_ phase -> ModIface_ phase)
-> ModIface_ phase -> ModIface_ phase
forall a b. (a -> b) -> a -> b
$ ModIface_ phase
iface { mi_mod_info_ = val }
set_mi_self_recomp :: Maybe IfaceSelfRecomp-> ModIface_ phase -> ModIface_ phase
set_mi_self_recomp :: forall (phase :: ModIfacePhase).
Maybe IfaceSelfRecomp -> ModIface_ phase -> ModIface_ phase
set_mi_self_recomp Maybe IfaceSelfRecomp
val ModIface_ phase
iface = ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes (ModIface_ phase -> ModIface_ phase)
-> ModIface_ phase -> ModIface_ phase
forall a b. (a -> b) -> a -> b
$ ModIface_ phase
iface { mi_self_recomp_ = val }
set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase
set_mi_hi_bytes :: forall (phase :: ModIfacePhase).
IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase
set_mi_hi_bytes IfaceBinHandle phase
val ModIface_ phase
iface = ModIface_ phase
iface { mi_hi_bytes_ = val }
set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase
set_mi_deps :: forall (phase :: ModIfacePhase).
Dependencies -> ModIface_ phase -> ModIface_ phase
set_mi_deps Dependencies
val ModIface_ phase
iface = ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes (ModIface_ phase -> ModIface_ phase)
-> ModIface_ phase -> ModIface_ phase
forall a b. (a -> b) -> a -> b
$ ModIface_ phase
iface { mi_deps_ = val }
set_mi_public :: (IfacePublic_ phase -> IfacePublic_ phase) -> ModIface_ phase -> ModIface_ phase
set_mi_public :: forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public IfacePublic_ phase -> IfacePublic_ phase
f ModIface_ phase
iface = ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes (ModIface_ phase -> ModIface_ phase)
-> ModIface_ phase -> ModIface_ phase
forall a b. (a -> b) -> a -> b
$ ModIface_ phase
iface { mi_public_ = f (mi_public_ iface) }
set_mi_simplified_core :: Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase
set_mi_simplified_core :: forall (phase :: ModIfacePhase).
Maybe IfaceSimplifiedCore -> ModIface_ phase -> ModIface_ phase
set_mi_simplified_core Maybe IfaceSimplifiedCore
val ModIface_ phase
iface = ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes (ModIface_ phase -> ModIface_ phase)
-> ModIface_ phase -> ModIface_ phase
forall a b. (a -> b) -> a -> b
$ ModIface_ phase
iface { mi_simplified_core_ = val }
set_mi_top_env :: IfaceTopEnv -> ModIface_ phase -> ModIface_ phase
set_mi_top_env :: forall (phase :: ModIfacePhase).
IfaceTopEnv -> ModIface_ phase -> ModIface_ phase
set_mi_top_env IfaceTopEnv
val ModIface_ phase
iface = ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes (ModIface_ phase -> ModIface_ phase)
-> ModIface_ phase -> ModIface_ phase
forall a b. (a -> b) -> a -> b
$ ModIface_ phase
iface { mi_top_env_ = val }
set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase
set_mi_docs :: forall (phase :: ModIfacePhase).
Maybe Docs -> ModIface_ phase -> ModIface_ phase
set_mi_docs Maybe Docs
val ModIface_ phase
iface = ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes (ModIface_ phase -> ModIface_ phase)
-> ModIface_ phase -> ModIface_ phase
forall a b. (a -> b) -> a -> b
$ ModIface_ phase
iface { mi_docs_ = val }
set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase
set_mi_ext_fields :: forall (phase :: ModIfacePhase).
ExtensibleFields -> ModIface_ phase -> ModIface_ phase
set_mi_ext_fields ExtensibleFields
val ModIface_ phase
iface = ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes (ModIface_ phase -> ModIface_ phase)
-> ModIface_ phase -> ModIface_ phase
forall a b. (a -> b) -> a -> b
$ ModIface_ phase
iface { mi_ext_fields_ = val }
set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase
set_mi_exports :: forall (phase :: ModIfacePhase).
[IfaceExport] -> ModIface_ phase -> ModIface_ phase
set_mi_exports [IfaceExport]
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_exports_ = val })
set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase
set_mi_fixities :: forall (phase :: ModIfacePhase).
[(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase
set_mi_fixities [(OccName, Fixity)]
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_fixities_ = val })
set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase
set_mi_warns :: forall (phase :: ModIfacePhase).
IfaceWarnings -> ModIface_ phase -> ModIface_ phase
set_mi_warns IfaceWarnings
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_warns_ = val })
set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase
set_mi_anns :: forall (phase :: ModIfacePhase).
[IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase
set_mi_anns [IfaceAnnotation]
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_anns_ = val })
set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase
set_mi_insts :: forall (phase :: ModIfacePhase).
[IfaceClsInst] -> ModIface_ phase -> ModIface_ phase
set_mi_insts [IfaceClsInst]
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_insts_ = val })
set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase
set_mi_fam_insts :: forall (phase :: ModIfacePhase).
[IfaceFamInst] -> ModIface_ phase -> ModIface_ phase
set_mi_fam_insts [IfaceFamInst]
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_fam_insts_ = val })
set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase
set_mi_rules :: forall (phase :: ModIfacePhase).
[IfaceRule] -> ModIface_ phase -> ModIface_ phase
set_mi_rules [IfaceRule]
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_rules_ = val })
set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase
set_mi_decls :: forall (phase :: ModIfacePhase).
[IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase
set_mi_decls [IfaceDeclExts phase]
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_decls_ = val })
set_mi_defaults :: [IfaceDefault] -> ModIface_ phase -> ModIface_ phase
set_mi_defaults :: forall (phase :: ModIfacePhase).
[IfaceDefault] -> ModIface_ phase -> ModIface_ phase
set_mi_defaults [IfaceDefault]
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_defaults_ = val })
set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase
set_mi_trust :: forall (phase :: ModIfacePhase).
IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase
set_mi_trust IfaceTrustInfo
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_trust_ = val })
set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase
set_mi_trust_pkg :: forall (phase :: ModIfacePhase).
WhetherHasOrphans -> ModIface_ phase -> ModIface_ phase
set_mi_trust_pkg WhetherHasOrphans
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_trust_pkg_ = val })
set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase
set_mi_complete_matches :: forall (phase :: ModIfacePhase).
[IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase
set_mi_complete_matches [IfaceCompleteMatch]
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_complete_matches_ = val })
set_mi_abi_hashes :: IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase
set_mi_abi_hashes :: forall (phase :: ModIfacePhase).
IfaceAbiHashesExts phase -> ModIface_ phase -> ModIface_ phase
set_mi_abi_hashes IfaceAbiHashesExts phase
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_abi_hashes_ = val })
set_mi_decl_warn_fn :: (OccName -> Maybe (WarningTxt GhcRn)) -> ModIface_ phase -> ModIface_ phase
set_mi_decl_warn_fn :: forall (phase :: ModIfacePhase).
(OccName -> Maybe (WarningTxt GhcRn))
-> ModIface_ phase -> ModIface_ phase
set_mi_decl_warn_fn OccName -> Maybe (WarningTxt GhcRn)
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_caches_ = (mi_caches_ iface) { mi_cache_decl_warn_fn = val } })
set_mi_export_warn_fn :: (Name -> 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_export_warn_fn Name -> Maybe (WarningTxt GhcRn)
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_caches_ = (mi_caches_ iface) { mi_cache_export_warn_fn = val } })
set_mi_fix_fn :: (OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase
set_mi_fix_fn :: forall (phase :: ModIfacePhase).
(OccName -> Maybe Fixity) -> ModIface_ phase -> ModIface_ phase
set_mi_fix_fn OccName -> Maybe Fixity
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_caches_ = (mi_caches_ iface) { mi_cache_fix_fn = val } })
set_mi_hash_fn :: (OccName -> Maybe (OccName, Fingerprint)) -> ModIface_ phase -> ModIface_ phase
set_mi_hash_fn :: forall (phase :: ModIfacePhase).
(OccName -> Maybe (OccName, Fingerprint))
-> ModIface_ phase -> ModIface_ phase
set_mi_hash_fn OccName -> Maybe (OccName, Fingerprint)
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_caches_ = (mi_caches_ iface) { mi_cache_hash_fn = val } })
set_mi_caches :: IfaceCache -> ModIface_ phase -> ModIface_ phase
set_mi_caches :: forall (phase :: ModIfacePhase).
IfaceCache -> ModIface_ phase -> ModIface_ phase
set_mi_caches IfaceCache
val = (IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfacePublic_ phase -> IfacePublic_ phase)
-> ModIface_ phase -> ModIface_ phase
set_mi_public (\IfacePublic_ phase
iface -> IfacePublic_ phase
iface { mi_caches_ = val })
set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase
set_mi_module :: forall (phase :: ModIfacePhase).
Module -> ModIface_ phase -> ModIface_ phase
set_mi_module Module
val = (IfaceModInfo -> IfaceModInfo)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfaceModInfo -> IfaceModInfo)
-> ModIface_ phase -> ModIface_ phase
set_mi_mod_info_field (\IfaceModInfo
info -> IfaceModInfo
info { mi_mod_info_module = val })
set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase
set_mi_sig_of :: forall (phase :: ModIfacePhase).
Maybe Module -> ModIface_ phase -> ModIface_ phase
set_mi_sig_of Maybe Module
val = (IfaceModInfo -> IfaceModInfo)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfaceModInfo -> IfaceModInfo)
-> ModIface_ phase -> ModIface_ phase
set_mi_mod_info_field (\IfaceModInfo
info -> IfaceModInfo
info { mi_mod_info_sig_of = val })
set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase
set_mi_hsc_src :: forall (phase :: ModIfacePhase).
HscSource -> ModIface_ phase -> ModIface_ phase
set_mi_hsc_src HscSource
val = (IfaceModInfo -> IfaceModInfo)
-> ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase).
(IfaceModInfo -> IfaceModInfo)
-> ModIface_ phase -> ModIface_ phase
set_mi_mod_info_field (\IfaceModInfo
info -> IfaceModInfo
info { mi_mod_info_hsc_src = val })
set_mi_mod_info_field :: (IfaceModInfo -> IfaceModInfo) -> ModIface_ phase -> ModIface_ phase
set_mi_mod_info_field :: forall (phase :: ModIfacePhase).
(IfaceModInfo -> IfaceModInfo)
-> ModIface_ phase -> ModIface_ phase
set_mi_mod_info_field IfaceModInfo -> IfaceModInfo
f ModIface_ phase
iface = ModIface_ phase -> ModIface_ phase
forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes (ModIface_ phase -> ModIface_ phase)
-> ModIface_ phase -> ModIface_ phase
forall a b. (a -> b) -> a -> b
$ ModIface_ phase
iface { mi_mod_info_ = f (mi_mod_info_ iface) }
clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes :: forall (phase :: ModIfacePhase). ModIface_ phase -> ModIface_ phase
clear_mi_hi_bytes ModIface_ phase
iface = ModIface_ phase
iface
{ mi_hi_bytes_ = case mi_hi_bytes iface of
IfaceBinHandle phase
PartialIfaceBinHandle -> IfaceBinHandle phase
IfaceBinHandle 'ModIfaceCore
PartialIfaceBinHandle
FullIfaceBinHandle Maybe FullBinData
_ -> Maybe FullBinData -> IfaceBinHandle 'ModIfaceFinal
FullIfaceBinHandle Maybe FullBinData
forall a. Maybe a
Strict.Nothing
}
{-# INLINE mi_mod_info #-}
{-# INLINE mi_iface_hash #-}
{-# INLINE mi_module #-}
{-# INLINE mi_sig_of #-}
{-# INLINE mi_hsc_src #-}
{-# INLINE mi_deps #-}
{-# INLINE mi_public #-}
{-# INLINE mi_exports #-}
{-# INLINE mi_fixities #-}
{-# INLINE mi_warns #-}
{-# INLINE mi_anns #-}
{-# INLINE mi_decls #-}
{-# INLINE mi_simplified_core #-}
{-# INLINE mi_defaults #-}
{-# INLINE mi_top_env #-}
{-# INLINE mi_insts #-}
{-# INLINE mi_fam_insts #-}
{-# INLINE mi_rules #-}
{-# INLINE mi_trust #-}
{-# INLINE mi_trust_pkg #-}
{-# INLINE mi_complete_matches #-}
{-# INLINE mi_docs #-}
{-# INLINE mi_abi_hashes #-}
{-# INLINE mi_ext_fields #-}
{-# INLINE mi_hi_bytes #-}
{-# INLINE mi_self_recomp_info #-}
{-# INLINE mi_fix_fn #-}
{-# INLINE mi_hash_fn #-}
{-# INLINE mi_decl_warn_fn #-}
{-# INLINE mi_export_warn_fn #-}
{-# INLINE ModIface #-}
{-# COMPLETE 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
pattern $mModIface :: forall {r} {phase :: ModIfacePhase}.
ModIface_ phase
-> (IfaceModInfo
-> Module
-> Maybe Module
-> HscSource
-> Fingerprint
-> Dependencies
-> IfacePublic_ phase
-> [IfaceExport]
-> [(OccName, Fixity)]
-> IfaceWarnings
-> [IfaceAnnotation]
-> [IfaceDeclExts phase]
-> Maybe IfaceSimplifiedCore
-> [IfaceDefault]
-> IfaceTopEnv
-> [IfaceClsInst]
-> [IfaceFamInst]
-> [IfaceRule]
-> IfaceTrustInfo
-> WhetherHasOrphans
-> [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))
-> r)
-> ((# #) -> r)
-> r
ModIface
{ forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceModInfo
mi_mod_info
, forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module
, forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Module
mi_sig_of
, forall (phase :: ModIfacePhase). ModIface_ phase -> HscSource
mi_hsc_src
, forall (phase :: ModIfacePhase). ModIface_ phase -> Fingerprint
mi_iface_hash
, forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps
, forall (phase :: ModIfacePhase).
ModIface_ phase -> IfacePublic_ phase
mi_public
, forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceExport]
mi_exports
, forall (phase :: ModIfacePhase).
ModIface_ phase -> [(OccName, Fixity)]
mi_fixities
, forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceWarnings
mi_warns
, forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceAnnotation]
mi_anns
, forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceDeclExts phase]
mi_decls
, forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSimplifiedCore
mi_simplified_core
, forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceDefault]
mi_defaults
, forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTopEnv
mi_top_env
, forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceClsInst]
mi_insts
, forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceFamInst]
mi_fam_insts
, forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceRule]
mi_rules
, forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust
, forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_trust_pkg
, forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceCompleteMatch]
mi_complete_matches
, forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Docs
mi_docs
, forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceAbiHashesExts phase
mi_abi_hashes
, forall (phase :: ModIfacePhase).
ModIface_ phase -> ExtensibleFields
mi_ext_fields
, forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBinHandle phase
mi_hi_bytes
, forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfaceSelfRecomp
mi_self_recomp_info
, forall (phase :: ModIfacePhase).
ModIface_ phase -> OccName -> Maybe Fixity
mi_fix_fn
, forall (phase :: ModIfacePhase).
ModIface_ phase -> OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn
, forall (phase :: ModIfacePhase).
ModIface_ phase -> OccName -> Maybe (WarningTxt GhcRn)
mi_decl_warn_fn
, forall (phase :: ModIfacePhase).
ModIface_ phase -> Name -> Maybe (WarningTxt GhcRn)
mi_export_warn_fn
} <- PrivateModIface
{ mi_mod_info_ = mi_mod_info@IfaceModInfo { mi_mod_info_module = mi_module
, mi_mod_info_sig_of = mi_sig_of
, mi_mod_info_hsc_src = mi_hsc_src }
, mi_iface_hash_ = mi_iface_hash
, mi_deps_ = mi_deps
, mi_public_ = mi_public@IfacePublic {
mi_exports_ = mi_exports
, mi_fixities_ = mi_fixities
, mi_warns_ = mi_warns
, mi_anns_ = mi_anns
, mi_decls_ = mi_decls
, mi_defaults_ = mi_defaults
, mi_insts_ = mi_insts
, mi_fam_insts_ = mi_fam_insts
, mi_rules_ = mi_rules
, mi_trust_ = mi_trust
, mi_trust_pkg_ = mi_trust_pkg
, mi_complete_matches_ = mi_complete_matches
, mi_caches_ = IfaceCache {
mi_cache_decl_warn_fn = mi_decl_warn_fn,
mi_cache_export_warn_fn = mi_export_warn_fn,
mi_cache_fix_fn = mi_fix_fn,
mi_cache_hash_fn = mi_hash_fn
}
, mi_abi_hashes_ = mi_abi_hashes
}
, mi_docs_ = mi_docs
, mi_ext_fields_ = mi_ext_fields
, mi_hi_bytes_ = mi_hi_bytes
, mi_self_recomp_ = mi_self_recomp_info
, mi_simplified_core_ = mi_simplified_core
, mi_top_env_ = mi_top_env
}