{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NamedFieldPuns #-}
module GHC.Unit.Module.ModIface
   ( ModIface
   , ModIface_ (..)
   , PartialModIface
   , ModIfaceBackend (..)
   , IfaceDeclExts
   , IfaceBackendExts
   , IfaceExport
   , WhetherHasOrphans
   , WhetherHasFamInst
   , mi_boot
   , mi_fix
   , mi_semantic_module
   , mi_free_holes
   , mi_mnwib
   , renameFreeHoles
   , emptyPartialModIface
   , emptyFullModIface
   , mkIfaceHashCache
   , emptyIfaceHashCache
   , forceModIface
   )
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
import Control.Exception
type PartialModIface = ModIface_ 'ModIfaceCore
type ModIface = ModIface_ 'ModIfaceFinal
data ModIfaceBackend = ModIfaceBackend
  { ModIfaceBackend -> Fingerprint
mi_iface_hash :: !Fingerprint
    
  , ModIfaceBackend -> Fingerprint
mi_mod_hash :: !Fingerprint
    
  , ModIfaceBackend -> Fingerprint
mi_flag_hash :: !Fingerprint
    
    
  , ModIfaceBackend -> Fingerprint
mi_opt_hash :: !Fingerprint
    
  , ModIfaceBackend -> Fingerprint
mi_hpc_hash :: !Fingerprint
    
  , ModIfaceBackend -> Fingerprint
mi_plugin_hash :: !Fingerprint
    
  , ModIfaceBackend -> WhetherHasOrphans
mi_orphan :: !WhetherHasOrphans
    
  , ModIfaceBackend -> WhetherHasOrphans
mi_finsts :: !WhetherHasFamInst
    
    
  , ModIfaceBackend -> Fingerprint
mi_exp_hash :: !Fingerprint
    
  , ModIfaceBackend -> Fingerprint
mi_orphan_hash :: !Fingerprint
    
    
    
    
    
  , ModIfaceBackend -> OccName -> Maybe (WarningTxt GhcRn)
mi_decl_warn_fn :: !(OccName -> Maybe (WarningTxt GhcRn))
    
  , ModIfaceBackend -> Name -> Maybe (WarningTxt GhcRn)
mi_export_warn_fn :: !(Name -> Maybe (WarningTxt GhcRn))
    
  , ModIfaceBackend -> OccName -> Maybe Fixity
mi_fix_fn :: !(OccName -> Maybe Fixity)
    
  , ModIfaceBackend -> OccName -> Maybe (OccName, Fingerprint)
mi_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 IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where
  IfaceBackendExts 'ModIfaceCore = ()
  IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend
data ModIface_ (phase :: ModIfacePhase)
  = ModIface {
        forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module     :: !Module,             
        forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Module
mi_sig_of     :: !(Maybe Module),     
        forall (phase :: ModIfacePhase). ModIface_ phase -> HscSource
mi_hsc_src    :: !HscSource,          
        forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps     :: Dependencies,
                
                
                
        forall (phase :: ModIfacePhase). ModIface_ phase -> [Usage]
mi_usages   :: [Usage],
                
                
                
                
                
        forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceExport]
mi_exports  :: ![IfaceExport],
                
                
                
                
        forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_used_th  :: !Bool,
                
                
        forall (phase :: ModIfacePhase).
ModIface_ phase -> [(OccName, Fixity)]
mi_fixities :: [(OccName,Fixity)],
                
                
        forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceWarnings
mi_warns    :: IfaceWarnings,
                
                
        forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceAnnotation]
mi_anns     :: [IfaceAnnotation],
                
                
        forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceDeclExts phase]
mi_decls    :: [IfaceDeclExts phase],
                
                
                
                
                
         :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo],
                
                
                
        forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfGlobalRdrEnv
mi_globals  :: !(Maybe IfGlobalRdrEnv),
                
                
                
                
                
                
                
                
                
                
                
                
                
                
        forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceClsInst]
mi_insts       :: [IfaceClsInst],     
        forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceFamInst]
mi_fam_insts   :: [IfaceFamInst],  
        forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceRule]
mi_rules       :: [IfaceRule],     
        forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_hpc       :: !AnyHpcUsage,
                
        forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust     :: !IfaceTrustInfo,
                
        forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_trust_pkg :: !Bool,
                
                
                
                
                
                
        forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceCompleteMatch]
mi_complete_matches :: ![IfaceCompleteMatch],
        forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Docs
mi_docs :: !(Maybe Docs),
                
                
                
                
        forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts :: !(IfaceBackendExts phase),
                
                
        forall (phase :: ModIfacePhase).
ModIface_ phase -> ExtensibleFields
mi_ext_fields :: !ExtensibleFields,
                
                
                
                
                
                
                
        forall (phase :: ModIfacePhase). ModIface_ phase -> Fingerprint
mi_src_hash :: !Fingerprint
                
     }
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 = ModIfaceBackend -> OccName -> Maybe Fixity
mi_fix_fn (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface) OccName
name Maybe Fixity -> Fixity -> Fixity
forall a. Maybe a -> a -> a
`orElse` Fixity
defaultFixity
mi_semantic_module :: ModIface_ a -> Module
mi_semantic_module :: forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_semantic_module ModIface_ a
iface = case ModIface_ a -> Maybe Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Module
mi_sig_of ModIface_ a
iface of
                            Maybe Module
Nothing -> ModIface_ a -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface_ a
iface
                            Just Module
mod -> Module
mod
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_ :: BinHandle -> ModIface -> IO ()
put_ BinHandle
bh (ModIface {
                 mi_module :: forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module    = Module
mod,
                 mi_sig_of :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Module
mi_sig_of    = Maybe Module
sig_of,
                 mi_hsc_src :: forall (phase :: ModIfacePhase). ModIface_ phase -> HscSource
mi_hsc_src   = HscSource
hsc_src,
                 mi_src_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Fingerprint
mi_src_hash = Fingerprint
_src_hash, 
                                          
                                          
                 mi_deps :: forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps      = Dependencies
deps,
                 mi_usages :: forall (phase :: ModIfacePhase). ModIface_ phase -> [Usage]
mi_usages    = [Usage]
usages,
                 mi_exports :: forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceExport]
mi_exports   = [IfaceExport]
exports,
                 mi_used_th :: forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_used_th   = WhetherHasOrphans
used_th,
                 mi_fixities :: forall (phase :: ModIfacePhase).
ModIface_ phase -> [(OccName, Fixity)]
mi_fixities  = [(OccName, Fixity)]
fixities,
                 mi_warns :: forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceWarnings
mi_warns     = IfaceWarnings
warns,
                 mi_anns :: forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceAnnotation]
mi_anns      = [IfaceAnnotation]
anns,
                 mi_decls :: forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceDeclExts phase]
mi_decls     = [IfaceDeclExts 'ModIfaceFinal]
decls,
                 mi_extra_decls :: forall (phase :: ModIfacePhase).
ModIface_ phase
-> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
mi_extra_decls = Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
extra_decls,
                 mi_insts :: forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceClsInst]
mi_insts     = [IfaceClsInst]
insts,
                 mi_fam_insts :: forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceFamInst]
mi_fam_insts = [IfaceFamInst]
fam_insts,
                 mi_rules :: forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceRule]
mi_rules     = [IfaceRule]
rules,
                 mi_hpc :: forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_hpc       = WhetherHasOrphans
hpc_info,
                 mi_trust :: forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust     = IfaceTrustInfo
trust,
                 mi_trust_pkg :: forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_trust_pkg = WhetherHasOrphans
trust_pkg,
                 mi_complete_matches :: forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceCompleteMatch]
mi_complete_matches = [IfaceCompleteMatch]
complete_matches,
                 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_final_exts :: forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts = ModIfaceBackend {
                   mi_iface_hash :: ModIfaceBackend -> Fingerprint
mi_iface_hash = Fingerprint
iface_hash,
                   mi_mod_hash :: ModIfaceBackend -> Fingerprint
mi_mod_hash = Fingerprint
mod_hash,
                   mi_flag_hash :: ModIfaceBackend -> Fingerprint
mi_flag_hash = Fingerprint
flag_hash,
                   mi_opt_hash :: ModIfaceBackend -> Fingerprint
mi_opt_hash = Fingerprint
opt_hash,
                   mi_hpc_hash :: ModIfaceBackend -> Fingerprint
mi_hpc_hash = Fingerprint
hpc_hash,
                   mi_plugin_hash :: ModIfaceBackend -> Fingerprint
mi_plugin_hash = Fingerprint
plugin_hash,
                   mi_orphan :: ModIfaceBackend -> WhetherHasOrphans
mi_orphan = WhetherHasOrphans
orphan,
                   mi_finsts :: ModIfaceBackend -> WhetherHasOrphans
mi_finsts = WhetherHasOrphans
hasFamInsts,
                   mi_exp_hash :: ModIfaceBackend -> Fingerprint
mi_exp_hash = Fingerprint
exp_hash,
                   mi_orphan_hash :: ModIfaceBackend -> Fingerprint
mi_orphan_hash = Fingerprint
orphan_hash
                 }}) = do
        BinHandle -> Module -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Module
mod
        BinHandle -> Maybe Module -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Module
sig_of
        BinHandle -> HscSource -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh HscSource
hsc_src
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
iface_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
mod_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
flag_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
opt_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
hpc_hash
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
plugin_hash
        BinHandle -> WhetherHasOrphans -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh WhetherHasOrphans
orphan
        BinHandle -> WhetherHasOrphans -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh WhetherHasOrphans
hasFamInsts
        BinHandle -> Dependencies -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh Dependencies
deps
        BinHandle -> [Usage] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh [Usage]
usages
        BinHandle -> [IfaceExport] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceExport]
exports
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
exp_hash
        BinHandle -> WhetherHasOrphans -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh WhetherHasOrphans
used_th
        BinHandle -> [(OccName, Fixity)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [(OccName, Fixity)]
fixities
        BinHandle -> IfaceWarnings -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh IfaceWarnings
warns
        BinHandle -> [IfaceAnnotation] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh [IfaceAnnotation]
anns
        BinHandle -> [(Fingerprint, IfaceDecl)] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [(Fingerprint, IfaceDecl)]
[IfaceDeclExts 'ModIfaceFinal]
decls
        BinHandle
-> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
extra_decls
        BinHandle -> [IfaceClsInst] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceClsInst]
insts
        BinHandle -> [IfaceFamInst] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceFamInst]
fam_insts
        BinHandle -> [IfaceRule] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
lazyPut BinHandle
bh [IfaceRule]
rules
        BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Fingerprint
orphan_hash
        BinHandle -> WhetherHasOrphans -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh WhetherHasOrphans
hpc_info
        BinHandle -> IfaceTrustInfo -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh IfaceTrustInfo
trust
        BinHandle -> WhetherHasOrphans -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh WhetherHasOrphans
trust_pkg
        BinHandle -> [IfaceCompleteMatch] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceCompleteMatch]
complete_matches
        BinHandle -> Maybe Docs -> IO ()
forall a. Binary a => BinHandle -> Maybe a -> IO ()
lazyPutMaybe BinHandle
bh Maybe Docs
docs
   get :: BinHandle -> IO ModIface
get BinHandle
bh = do
        mod         <- BinHandle -> IO Module
forall a. Binary a => BinHandle -> IO a
get BinHandle
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      <- {-# SCC "bin_usages" #-} lazyGet bh
        exports     <- {-# SCC "bin_exports" #-} get bh
        exp_hash    <- get bh
        used_th     <- get bh
        fixities    <- {-# SCC "bin_fixities" #-} get bh
        warns       <- {-# SCC "bin_warns" #-} lazyGet bh
        anns        <- {-# SCC "bin_anns" #-} lazyGet bh
        decls       <- {-# SCC "bin_tycldecls" #-} get bh
        extra_decls <- get bh
        insts       <- {-# SCC "bin_insts" #-} get bh
        fam_insts   <- {-# SCC "bin_fam_insts" #-} get bh
        rules       <- {-# SCC "bin_rules" #-} lazyGet bh
        orphan_hash <- get bh
        hpc_info    <- get bh
        trust       <- get bh
        trust_pkg   <- get bh
        complete_matches <- get bh
        docs        <- lazyGetMaybe bh
        return (ModIface {
                 mi_module      = mod,
                 mi_sig_of      = sig_of,
                 mi_hsc_src     = hsc_src,
                 mi_src_hash = fingerprint0, 
                                             
                 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_extra_decls = extra_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_docs        = 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_decl_warn_fn = mkIfaceDeclWarnCache $ fromIfaceWarnings warns,
                   mi_export_warn_fn = mkIfaceExportWarnCache $ fromIfaceWarnings warns,
                   mi_fix_fn = mkIfaceFixCache fixities,
                   mi_hash_fn = mkIfaceHashCache decls
                 }})
type IfaceExport = AvailInfo
emptyPartialModIface :: Module -> PartialModIface
emptyPartialModIface :: Module -> PartialModIface
emptyPartialModIface Module
mod
  = ModIface { mi_module :: Module
mi_module      = Module
mod,
               mi_sig_of :: Maybe Module
mi_sig_of      = Maybe Module
forall a. Maybe a
Nothing,
               mi_hsc_src :: HscSource
mi_hsc_src     = HscSource
HsSrcFile,
               mi_src_hash :: Fingerprint
mi_src_hash    = Fingerprint
fingerprint0,
               mi_deps :: Dependencies
mi_deps        = Dependencies
noDependencies,
               mi_usages :: [Usage]
mi_usages      = [],
               mi_exports :: [IfaceExport]
mi_exports     = [],
               mi_used_th :: WhetherHasOrphans
mi_used_th     = WhetherHasOrphans
False,
               mi_fixities :: [(OccName, Fixity)]
mi_fixities    = [],
               mi_warns :: IfaceWarnings
mi_warns       = [(OccName, IfaceWarningTxt)]
-> [(Name, IfaceWarningTxt)] -> IfaceWarnings
IfWarnSome [] [],
               mi_anns :: [IfaceAnnotation]
mi_anns        = [],
               mi_insts :: [IfaceClsInst]
mi_insts       = [],
               mi_fam_insts :: [IfaceFamInst]
mi_fam_insts   = [],
               mi_rules :: [IfaceRule]
mi_rules       = [],
               mi_decls :: [IfaceDeclExts 'ModIfaceCore]
mi_decls       = [],
               mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
mi_extra_decls = Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
forall a. Maybe a
Nothing,
               mi_globals :: Maybe IfGlobalRdrEnv
mi_globals     = Maybe IfGlobalRdrEnv
forall a. Maybe a
Nothing,
               mi_hpc :: WhetherHasOrphans
mi_hpc         = WhetherHasOrphans
False,
               mi_trust :: IfaceTrustInfo
mi_trust       = IfaceTrustInfo
noIfaceTrustInfo,
               mi_trust_pkg :: WhetherHasOrphans
mi_trust_pkg   = WhetherHasOrphans
False,
               mi_complete_matches :: [IfaceCompleteMatch]
mi_complete_matches = [],
               mi_docs :: Maybe Docs
mi_docs        = Maybe Docs
forall a. Maybe a
Nothing,
               mi_final_exts :: IfaceBackendExts 'ModIfaceCore
mi_final_exts  = (),
               mi_ext_fields :: ExtensibleFields
mi_ext_fields  = ExtensibleFields
emptyExtensibleFields
             }
emptyFullModIface :: Module -> ModIface
emptyFullModIface :: Module -> ModIface
emptyFullModIface Module
mod =
    (Module -> PartialModIface
emptyPartialModIface Module
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_decl_warn_fn = emptyIfaceWarnCache,
          mi_export_warn_fn = emptyIfaceWarnCache,
          mi_fix_fn = emptyIfaceFixCache,
          mi_hash_fn = emptyIfaceHashCache } }
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 (IfaceBackendExts (phase :: ModIfacePhase))
         , NFData (IfaceDeclExts (phase :: ModIfacePhase))
         ) => NFData (ModIface_ phase) where
  rnf :: ModIface_ phase -> ()
rnf (ModIface{ Module
mi_module :: forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module :: Module
mi_module, Maybe Module
mi_sig_of :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Module
mi_sig_of :: Maybe Module
mi_sig_of, HscSource
mi_hsc_src :: forall (phase :: ModIfacePhase). ModIface_ phase -> HscSource
mi_hsc_src :: HscSource
mi_hsc_src, Dependencies
mi_deps :: forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps :: Dependencies
mi_deps, [Usage]
mi_usages :: forall (phase :: ModIfacePhase). ModIface_ phase -> [Usage]
mi_usages :: [Usage]
mi_usages
               , [IfaceExport]
mi_exports :: forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceExport]
mi_exports :: [IfaceExport]
mi_exports, WhetherHasOrphans
mi_used_th :: forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_used_th :: WhetherHasOrphans
mi_used_th, [(OccName, Fixity)]
mi_fixities :: forall (phase :: ModIfacePhase).
ModIface_ phase -> [(OccName, Fixity)]
mi_fixities :: [(OccName, Fixity)]
mi_fixities, IfaceWarnings
mi_warns :: forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceWarnings
mi_warns :: IfaceWarnings
mi_warns, [IfaceAnnotation]
mi_anns :: forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceAnnotation]
mi_anns :: [IfaceAnnotation]
mi_anns
               , [IfaceDeclExts phase]
mi_decls :: forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceDeclExts phase]
mi_decls :: [IfaceDeclExts phase]
mi_decls, Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
mi_extra_decls :: forall (phase :: ModIfacePhase).
ModIface_ phase
-> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
mi_extra_decls, Maybe IfGlobalRdrEnv
mi_globals :: forall (phase :: ModIfacePhase).
ModIface_ phase -> Maybe IfGlobalRdrEnv
mi_globals :: Maybe IfGlobalRdrEnv
mi_globals, [IfaceClsInst]
mi_insts :: forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceClsInst]
mi_insts :: [IfaceClsInst]
mi_insts
               , [IfaceFamInst]
mi_fam_insts :: forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceFamInst]
mi_fam_insts :: [IfaceFamInst]
mi_fam_insts, [IfaceRule]
mi_rules :: forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceRule]
mi_rules :: [IfaceRule]
mi_rules, WhetherHasOrphans
mi_hpc :: forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_hpc :: WhetherHasOrphans
mi_hpc, IfaceTrustInfo
mi_trust :: forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust :: IfaceTrustInfo
mi_trust, WhetherHasOrphans
mi_trust_pkg :: forall (phase :: ModIfacePhase).
ModIface_ phase -> WhetherHasOrphans
mi_trust_pkg :: WhetherHasOrphans
mi_trust_pkg
               , [IfaceCompleteMatch]
mi_complete_matches :: forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceCompleteMatch]
mi_complete_matches :: [IfaceCompleteMatch]
mi_complete_matches, Maybe Docs
mi_docs :: forall (phase :: ModIfacePhase). ModIface_ phase -> Maybe Docs
mi_docs :: Maybe Docs
mi_docs, IfaceBackendExts phase
mi_final_exts :: forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts :: IfaceBackendExts phase
mi_final_exts
               , ExtensibleFields
mi_ext_fields :: forall (phase :: ModIfacePhase).
ModIface_ phase -> ExtensibleFields
mi_ext_fields :: ExtensibleFields
mi_ext_fields, Fingerprint
mi_src_hash :: forall (phase :: ModIfacePhase). ModIface_ phase -> Fingerprint
mi_src_hash :: Fingerprint
mi_src_hash })
    =     Module -> ()
forall a. NFData a => a -> ()
rnf Module
mi_module
    () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe Module -> ()
forall a. NFData a => a -> ()
rnf Maybe Module
mi_sig_of
    () -> () -> ()
forall a b. a -> b -> b
`seq`     HscSource
mi_hsc_src
    HscSource -> () -> ()
forall a b. a -> b -> b
`seq`     Dependencies
mi_deps
    Dependencies -> () -> ()
forall a b. a -> b -> b
`seq`     [Usage]
mi_usages
    [Usage] -> () -> ()
forall a b. a -> b -> b
`seq`     [IfaceExport]
mi_exports
    [IfaceExport] -> () -> ()
forall a b. a -> b -> b
`seq` WhetherHasOrphans -> ()
forall a. NFData a => a -> ()
rnf WhetherHasOrphans
mi_used_th
    () -> () -> ()
forall a b. a -> b -> b
`seq`     [(OccName, Fixity)]
mi_fixities
    [(OccName, Fixity)] -> () -> ()
forall a b. a -> b -> b
`seq` IfaceWarnings -> ()
forall a. NFData a => a -> ()
rnf IfaceWarnings
mi_warns
    () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceAnnotation] -> ()
forall a. NFData a => a -> ()
rnf [IfaceAnnotation]
mi_anns
    () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceDeclExts phase] -> ()
forall a. NFData a => a -> ()
rnf [IfaceDeclExts phase]
mi_decls
    () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ()
forall a. NFData a => a -> ()
rnf Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo]
mi_extra_decls
    () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe IfGlobalRdrEnv -> ()
forall a. NFData a => a -> ()
rnf Maybe IfGlobalRdrEnv
mi_globals
    () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceClsInst] -> ()
forall a. NFData a => a -> ()
rnf [IfaceClsInst]
mi_insts
    () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceFamInst] -> ()
forall a. NFData a => a -> ()
rnf [IfaceFamInst]
mi_fam_insts
    () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceRule] -> ()
forall a. NFData a => a -> ()
rnf [IfaceRule]
mi_rules
    () -> () -> ()
forall a b. a -> b -> b
`seq` WhetherHasOrphans -> ()
forall a. NFData a => a -> ()
rnf WhetherHasOrphans
mi_hpc
    () -> () -> ()
forall a b. a -> b -> b
`seq`     IfaceTrustInfo
mi_trust
    IfaceTrustInfo -> () -> ()
forall a b. a -> b -> b
`seq` WhetherHasOrphans -> ()
forall a. NFData a => a -> ()
rnf WhetherHasOrphans
mi_trust_pkg
    () -> () -> ()
forall a b. a -> b -> b
`seq` [IfaceCompleteMatch] -> ()
forall a. NFData a => a -> ()
rnf [IfaceCompleteMatch]
mi_complete_matches
    () -> () -> ()
forall a b. a -> b -> b
`seq` Maybe Docs -> ()
forall a. NFData a => a -> ()
rnf Maybe Docs
mi_docs
    () -> () -> ()
forall a b. a -> b -> b
`seq`     IfaceBackendExts phase
mi_final_exts
    IfaceBackendExts phase -> () -> ()
forall a b. a -> b -> b
`seq`     ExtensibleFields
mi_ext_fields
    ExtensibleFields -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
mi_src_hash
    () -> () -> ()
forall a b. a -> b -> b
`seq` ()
instance NFData (ModIfaceBackend) where
  rnf :: ModIfaceBackend -> ()
rnf (ModIfaceBackend{ Fingerprint
mi_iface_hash :: ModIfaceBackend -> Fingerprint
mi_iface_hash :: Fingerprint
mi_iface_hash, Fingerprint
mi_mod_hash :: ModIfaceBackend -> Fingerprint
mi_mod_hash :: Fingerprint
mi_mod_hash, Fingerprint
mi_flag_hash :: ModIfaceBackend -> Fingerprint
mi_flag_hash :: Fingerprint
mi_flag_hash, Fingerprint
mi_opt_hash :: ModIfaceBackend -> Fingerprint
mi_opt_hash :: Fingerprint
mi_opt_hash
                      , Fingerprint
mi_hpc_hash :: ModIfaceBackend -> Fingerprint
mi_hpc_hash :: Fingerprint
mi_hpc_hash, Fingerprint
mi_plugin_hash :: ModIfaceBackend -> Fingerprint
mi_plugin_hash :: Fingerprint
mi_plugin_hash, WhetherHasOrphans
mi_orphan :: ModIfaceBackend -> WhetherHasOrphans
mi_orphan :: WhetherHasOrphans
mi_orphan, WhetherHasOrphans
mi_finsts :: ModIfaceBackend -> WhetherHasOrphans
mi_finsts :: WhetherHasOrphans
mi_finsts, Fingerprint
mi_exp_hash :: ModIfaceBackend -> Fingerprint
mi_exp_hash :: Fingerprint
mi_exp_hash
                      , Fingerprint
mi_orphan_hash :: ModIfaceBackend -> Fingerprint
mi_orphan_hash :: Fingerprint
mi_orphan_hash, OccName -> Maybe (WarningTxt GhcRn)
mi_decl_warn_fn :: ModIfaceBackend -> OccName -> Maybe (WarningTxt GhcRn)
mi_decl_warn_fn :: OccName -> Maybe (WarningTxt GhcRn)
mi_decl_warn_fn, Name -> Maybe (WarningTxt GhcRn)
mi_export_warn_fn :: ModIfaceBackend -> Name -> Maybe (WarningTxt GhcRn)
mi_export_warn_fn :: Name -> Maybe (WarningTxt GhcRn)
mi_export_warn_fn, OccName -> Maybe Fixity
mi_fix_fn :: ModIfaceBackend -> OccName -> Maybe Fixity
mi_fix_fn :: OccName -> Maybe Fixity
mi_fix_fn
                      , OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn :: ModIfaceBackend -> OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn})
    =     Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
mi_iface_hash
    () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
mi_mod_hash
    () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
mi_flag_hash
    () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
mi_opt_hash
    () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
mi_hpc_hash
    () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
mi_plugin_hash
    () -> () -> ()
forall a b. a -> b -> b
`seq` WhetherHasOrphans -> ()
forall a. NFData a => a -> ()
rnf WhetherHasOrphans
mi_orphan
    () -> () -> ()
forall a b. a -> b -> b
`seq` WhetherHasOrphans -> ()
forall a. NFData a => a -> ()
rnf WhetherHasOrphans
mi_finsts
    () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
mi_exp_hash
    () -> () -> ()
forall a b. a -> b -> b
`seq` Fingerprint -> ()
forall a. NFData a => a -> ()
rnf Fingerprint
mi_orphan_hash
    () -> () -> ()
forall a b. a -> b -> b
`seq` (OccName -> Maybe (WarningTxt GhcRn)) -> ()
forall a. NFData a => a -> ()
rnf OccName -> Maybe (WarningTxt GhcRn)
mi_decl_warn_fn
    () -> () -> ()
forall a b. a -> b -> b
`seq` (Name -> Maybe (WarningTxt GhcRn)) -> ()
forall a. NFData a => a -> ()
rnf Name -> Maybe (WarningTxt GhcRn)
mi_export_warn_fn
    () -> () -> ()
forall a b. a -> b -> b
`seq` (OccName -> Maybe Fixity) -> ()
forall a. NFData a => a -> ()
rnf OccName -> Maybe Fixity
mi_fix_fn
    () -> () -> ()
forall a b. a -> b -> b
`seq` (OccName -> Maybe (OccName, Fingerprint)) -> ()
forall a. NFData a => a -> ()
rnf OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn
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