{-# LANGUAGE CPP, NondecreasingIndentation #-}
{-# LANGUAGE MultiWayIf #-}
module MkIface (
mkPartialIface,
mkFullIface,
mkIfaceTc,
writeIfaceFile,
checkOldIface,
RecompileRequired(..), recompileRequired,
mkIfaceExports,
coAxiomToIfaceDecl,
tyThingToIfaceDecl
) where
#include "HsVersions.h"
import GhcPrelude
import IfaceSyn
import BinFingerprint
import LoadIface
import ToIface
import FlagChecker
import DsUsage ( mkUsageInfo, mkUsedNames, mkDependencies )
import Id
import Annotations
import CoreSyn
import Class
import TyCon
import CoAxiom
import ConLike
import DataCon
import Type
import TcType
import InstEnv
import FamInstEnv
import TcRnMonad
import GHC.Hs
import HscTypes
import Finder
import DynFlags
import VarEnv
import Var
import Name
import Avail
import RdrName
import NameEnv
import NameSet
import Module
import BinIface
import ErrUtils
import Digraph
import SrcLoc
import Outputable
import BasicTypes hiding ( SuccessFlag(..) )
import Unique
import Util hiding ( eqListBy )
import FastString
import Maybes
import Binary
import Fingerprint
import Exception
import UniqSet
import Packages
import ExtractDocs
import Control.Monad
import Data.Function
import Data.List (find, findIndex, mapAccumL, sortBy, sort)
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Ord
import Data.IORef
import System.Directory
import System.FilePath
import Plugins ( PluginRecompile(..), PluginWithArgs(..), LoadedPlugin(..),
pluginRecompile', plugins )
import qualified Data.Semigroup
mkPartialIface :: HscEnv
-> ModDetails
-> ModGuts
-> PartialModIface
mkPartialIface :: HscEnv -> ModDetails -> ModGuts -> PartialModIface
mkPartialIface HscEnv
hsc_env ModDetails
mod_details
ModGuts{ mg_module :: ModGuts -> Module
mg_module = Module
this_mod
, mg_hsc_src :: ModGuts -> HscSource
mg_hsc_src = HscSource
hsc_src
, mg_usages :: ModGuts -> [Usage]
mg_usages = [Usage]
usages
, mg_used_th :: ModGuts -> Bool
mg_used_th = Bool
used_th
, mg_deps :: ModGuts -> Dependencies
mg_deps = Dependencies
deps
, mg_rdr_env :: ModGuts -> GlobalRdrEnv
mg_rdr_env = GlobalRdrEnv
rdr_env
, mg_fix_env :: ModGuts -> FixityEnv
mg_fix_env = FixityEnv
fix_env
, mg_warns :: ModGuts -> Warnings
mg_warns = Warnings
warns
, mg_hpc_info :: ModGuts -> HpcInfo
mg_hpc_info = HpcInfo
hpc_info
, mg_safe_haskell :: ModGuts -> SafeHaskellMode
mg_safe_haskell = SafeHaskellMode
safe_mode
, mg_trust_pkg :: ModGuts -> Bool
mg_trust_pkg = Bool
self_trust
, mg_doc_hdr :: ModGuts -> Maybe HsDocString
mg_doc_hdr = Maybe HsDocString
doc_hdr
, mg_decl_docs :: ModGuts -> DeclDocMap
mg_decl_docs = DeclDocMap
decl_docs
, mg_arg_docs :: ModGuts -> ArgDocMap
mg_arg_docs = ArgDocMap
arg_docs
}
= HscEnv
-> Module
-> HscSource
-> Bool
-> Dependencies
-> GlobalRdrEnv
-> FixityEnv
-> Warnings
-> HpcInfo
-> Bool
-> SafeHaskellMode
-> [Usage]
-> Maybe HsDocString
-> DeclDocMap
-> ArgDocMap
-> ModDetails
-> PartialModIface
mkIface_ HscEnv
hsc_env Module
this_mod HscSource
hsc_src Bool
used_th Dependencies
deps GlobalRdrEnv
rdr_env FixityEnv
fix_env Warnings
warns HpcInfo
hpc_info Bool
self_trust
SafeHaskellMode
safe_mode [Usage]
usages Maybe HsDocString
doc_hdr DeclDocMap
decl_docs ArgDocMap
arg_docs ModDetails
mod_details
mkFullIface :: HscEnv -> PartialModIface -> IO ModIface
mkFullIface :: HscEnv -> PartialModIface -> IO ModIface
mkFullIface HscEnv
hsc_env PartialModIface
partial_iface = do
ModIface
full_iface <-
{-# SCC "addFingerprints" #-}
HscEnv -> PartialModIface -> IO ModIface
addFingerprints HscEnv
hsc_env PartialModIface
partial_iface
DynFlags -> DumpFlag -> String -> SDoc -> IO ()
dumpIfSet_dyn (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) DumpFlag
Opt_D_dump_hi String
"FINAL INTERFACE" (ModIface -> SDoc
pprModIface ModIface
full_iface)
ModIface -> IO ModIface
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
full_iface
mkIfaceTc :: HscEnv
-> SafeHaskellMode
-> ModDetails
-> TcGblEnv
-> IO ModIface
mkIfaceTc :: HscEnv -> SafeHaskellMode -> ModDetails -> TcGblEnv -> IO ModIface
mkIfaceTc HscEnv
hsc_env SafeHaskellMode
safe_mode ModDetails
mod_details
tc_result :: TcGblEnv
tc_result@TcGblEnv{ tcg_mod :: TcGblEnv -> Module
tcg_mod = Module
this_mod,
tcg_src :: TcGblEnv -> HscSource
tcg_src = HscSource
hsc_src,
tcg_imports :: TcGblEnv -> ImportAvails
tcg_imports = ImportAvails
imports,
tcg_rdr_env :: TcGblEnv -> GlobalRdrEnv
tcg_rdr_env = GlobalRdrEnv
rdr_env,
tcg_fix_env :: TcGblEnv -> FixityEnv
tcg_fix_env = FixityEnv
fix_env,
tcg_merged :: TcGblEnv -> [(Module, Fingerprint)]
tcg_merged = [(Module, Fingerprint)]
merged,
tcg_warns :: TcGblEnv -> Warnings
tcg_warns = Warnings
warns,
tcg_hpc :: TcGblEnv -> Bool
tcg_hpc = Bool
other_hpc_info,
tcg_th_splice_used :: TcGblEnv -> TcRef Bool
tcg_th_splice_used = TcRef Bool
tc_splice_used,
tcg_dependent_files :: TcGblEnv -> TcRef [String]
tcg_dependent_files = TcRef [String]
dependent_files
}
= do
let used_names :: NameSet
used_names = TcGblEnv -> NameSet
mkUsedNames TcGblEnv
tc_result
let pluginModules :: [ModIface]
pluginModules =
(LoadedPlugin -> ModIface) -> [LoadedPlugin] -> [ModIface]
forall a b. (a -> b) -> [a] -> [b]
map LoadedPlugin -> ModIface
lpModule (DynFlags -> [LoadedPlugin]
cachedPlugins (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env))
Dependencies
deps <- InstalledUnitId -> [Module] -> TcGblEnv -> IO Dependencies
mkDependencies
(DynFlags -> InstalledUnitId
thisInstalledUnitId (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env))
((ModIface -> Module) -> [ModIface] -> [Module]
forall a b. (a -> b) -> [a] -> [b]
map ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module [ModIface]
pluginModules) TcGblEnv
tc_result
let hpc_info :: HpcInfo
hpc_info = Bool -> HpcInfo
emptyHpcInfo Bool
other_hpc_info
Bool
used_th <- TcRef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef TcRef Bool
tc_splice_used
[String]
dep_files <- (TcRef [String] -> IO [String]
forall a. IORef a -> IO a
readIORef TcRef [String]
dependent_files)
[Usage]
usages <- HscEnv
-> Module
-> ImportedMods
-> NameSet
-> [String]
-> [(Module, Fingerprint)]
-> [ModIface]
-> IO [Usage]
mkUsageInfo HscEnv
hsc_env Module
this_mod (ImportAvails -> ImportedMods
imp_mods ImportAvails
imports) NameSet
used_names
[String]
dep_files [(Module, Fingerprint)]
merged [ModIface]
pluginModules
let (Maybe HsDocString
doc_hdr', DeclDocMap
doc_map, ArgDocMap
arg_map) = TcGblEnv -> (Maybe HsDocString, DeclDocMap, ArgDocMap)
extractDocs TcGblEnv
tc_result
let partial_iface :: PartialModIface
partial_iface = HscEnv
-> Module
-> HscSource
-> Bool
-> Dependencies
-> GlobalRdrEnv
-> FixityEnv
-> Warnings
-> HpcInfo
-> Bool
-> SafeHaskellMode
-> [Usage]
-> Maybe HsDocString
-> DeclDocMap
-> ArgDocMap
-> ModDetails
-> PartialModIface
mkIface_ HscEnv
hsc_env
Module
this_mod HscSource
hsc_src
Bool
used_th Dependencies
deps GlobalRdrEnv
rdr_env
FixityEnv
fix_env Warnings
warns HpcInfo
hpc_info
(ImportAvails -> Bool
imp_trust_own_pkg ImportAvails
imports) SafeHaskellMode
safe_mode [Usage]
usages
Maybe HsDocString
doc_hdr' DeclDocMap
doc_map ArgDocMap
arg_map
ModDetails
mod_details
HscEnv -> PartialModIface -> IO ModIface
mkFullIface HscEnv
hsc_env PartialModIface
partial_iface
mkIface_ :: HscEnv -> Module -> HscSource
-> Bool -> Dependencies -> GlobalRdrEnv
-> NameEnv FixItem -> Warnings -> HpcInfo
-> Bool
-> SafeHaskellMode
-> [Usage]
-> Maybe HsDocString
-> DeclDocMap
-> ArgDocMap
-> ModDetails
-> PartialModIface
mkIface_ :: HscEnv
-> Module
-> HscSource
-> Bool
-> Dependencies
-> GlobalRdrEnv
-> FixityEnv
-> Warnings
-> HpcInfo
-> Bool
-> SafeHaskellMode
-> [Usage]
-> Maybe HsDocString
-> DeclDocMap
-> ArgDocMap
-> ModDetails
-> PartialModIface
mkIface_ HscEnv
hsc_env
Module
this_mod HscSource
hsc_src Bool
used_th Dependencies
deps GlobalRdrEnv
rdr_env FixityEnv
fix_env Warnings
src_warns
HpcInfo
hpc_info Bool
pkg_trust_req SafeHaskellMode
safe_mode [Usage]
usages
Maybe HsDocString
doc_hdr DeclDocMap
decl_docs ArgDocMap
arg_docs
ModDetails{ md_insts :: ModDetails -> [ClsInst]
md_insts = [ClsInst]
insts,
md_fam_insts :: ModDetails -> [FamInst]
md_fam_insts = [FamInst]
fam_insts,
md_rules :: ModDetails -> [CoreRule]
md_rules = [CoreRule]
rules,
md_anns :: ModDetails -> [Annotation]
md_anns = [Annotation]
anns,
md_types :: ModDetails -> TypeEnv
md_types = TypeEnv
type_env,
md_exports :: ModDetails -> [AvailInfo]
md_exports = [AvailInfo]
exports,
md_complete_sigs :: ModDetails -> [CompleteMatch]
md_complete_sigs = [CompleteMatch]
complete_sigs }
= do
let semantic_mod :: Module
semantic_mod = DynFlags -> ModuleName -> Module
canonicalizeHomeModule (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) (Module -> ModuleName
moduleName Module
this_mod)
entities :: [TyThing]
entities = TypeEnv -> [TyThing]
typeEnvElts TypeEnv
type_env
decls :: [IfaceDecl]
decls = [ TyThing -> IfaceDecl
tyThingToIfaceDecl TyThing
entity
| TyThing
entity <- [TyThing]
entities,
let name :: Name
name = TyThing -> Name
forall a. NamedThing a => a -> Name
getName TyThing
entity,
Bool -> Bool
not (TyThing -> Bool
isImplicitTyThing TyThing
entity),
Bool -> Bool
not (Name -> Bool
isWiredInName Name
name),
Module -> Name -> Bool
nameIsLocalOrFrom Module
semantic_mod Name
name ]
fixities :: [(OccName, Fixity)]
fixities = ((OccName, Fixity) -> (OccName, Fixity) -> Ordering)
-> [(OccName, Fixity)] -> [(OccName, Fixity)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (((OccName, Fixity) -> OccName)
-> (OccName, Fixity) -> (OccName, Fixity) -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (OccName, Fixity) -> OccName
forall a b. (a, b) -> a
fst)
[(OccName
occ,Fixity
fix) | FixItem OccName
occ Fixity
fix <- FixityEnv -> [FixItem]
forall a. NameEnv a -> [a]
nameEnvElts FixityEnv
fix_env]
warns :: Warnings
warns = Warnings
src_warns
iface_rules :: [IfaceRule]
iface_rules = (CoreRule -> IfaceRule) -> [CoreRule] -> [IfaceRule]
forall a b. (a -> b) -> [a] -> [b]
map CoreRule -> IfaceRule
coreRuleToIfaceRule [CoreRule]
rules
iface_insts :: [IfaceClsInst]
iface_insts = (ClsInst -> IfaceClsInst) -> [ClsInst] -> [IfaceClsInst]
forall a b. (a -> b) -> [a] -> [b]
map ClsInst -> IfaceClsInst
instanceToIfaceInst ([ClsInst] -> [IfaceClsInst]) -> [ClsInst] -> [IfaceClsInst]
forall a b. (a -> b) -> a -> b
$ SafeHaskellMode -> [ClsInst] -> [ClsInst]
fixSafeInstances SafeHaskellMode
safe_mode [ClsInst]
insts
iface_fam_insts :: [IfaceFamInst]
iface_fam_insts = (FamInst -> IfaceFamInst) -> [FamInst] -> [IfaceFamInst]
forall a b. (a -> b) -> [a] -> [b]
map FamInst -> IfaceFamInst
famInstToIfaceFamInst [FamInst]
fam_insts
trust_info :: IfaceTrustInfo
trust_info = SafeHaskellMode -> IfaceTrustInfo
setSafeMode SafeHaskellMode
safe_mode
annotations :: [IfaceAnnotation]
annotations = (Annotation -> IfaceAnnotation)
-> [Annotation] -> [IfaceAnnotation]
forall a b. (a -> b) -> [a] -> [b]
map Annotation -> IfaceAnnotation
mkIfaceAnnotation [Annotation]
anns
icomplete_sigs :: [IfaceCompleteMatch]
icomplete_sigs = (CompleteMatch -> IfaceCompleteMatch)
-> [CompleteMatch] -> [IfaceCompleteMatch]
forall a b. (a -> b) -> [a] -> [b]
map CompleteMatch -> IfaceCompleteMatch
mkIfaceCompleteSig [CompleteMatch]
complete_sigs
ModIface :: forall (phase :: ModIfacePhase).
Module
-> Maybe Module
-> HscSource
-> Dependencies
-> [Usage]
-> [AvailInfo]
-> Bool
-> [(OccName, Fixity)]
-> Warnings
-> [IfaceAnnotation]
-> [IfaceDeclExts phase]
-> Maybe GlobalRdrEnv
-> [IfaceClsInst]
-> [IfaceFamInst]
-> [IfaceRule]
-> Bool
-> IfaceTrustInfo
-> Bool
-> [IfaceCompleteMatch]
-> Maybe HsDocString
-> DeclDocMap
-> ArgDocMap
-> IfaceBackendExts phase
-> ModIface_ phase
ModIface {
mi_module :: Module
mi_module = Module
this_mod,
mi_sig_of :: Maybe Module
mi_sig_of = if Module
semantic_mod Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
this_mod
then Maybe Module
forall a. Maybe a
Nothing
else Module -> Maybe Module
forall a. a -> Maybe a
Just Module
semantic_mod,
mi_hsc_src :: HscSource
mi_hsc_src = HscSource
hsc_src,
mi_deps :: Dependencies
mi_deps = Dependencies
deps,
mi_usages :: [Usage]
mi_usages = [Usage]
usages,
mi_exports :: [AvailInfo]
mi_exports = [AvailInfo] -> [AvailInfo]
mkIfaceExports [AvailInfo]
exports,
mi_insts :: [IfaceClsInst]
mi_insts = (IfaceClsInst -> IfaceClsInst -> Ordering)
-> [IfaceClsInst] -> [IfaceClsInst]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy IfaceClsInst -> IfaceClsInst -> Ordering
cmp_inst [IfaceClsInst]
iface_insts,
mi_fam_insts :: [IfaceFamInst]
mi_fam_insts = (IfaceFamInst -> IfaceFamInst -> Ordering)
-> [IfaceFamInst] -> [IfaceFamInst]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy IfaceFamInst -> IfaceFamInst -> Ordering
cmp_fam_inst [IfaceFamInst]
iface_fam_insts,
mi_rules :: [IfaceRule]
mi_rules = (IfaceRule -> IfaceRule -> Ordering) -> [IfaceRule] -> [IfaceRule]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy IfaceRule -> IfaceRule -> Ordering
cmp_rule [IfaceRule]
iface_rules,
mi_fixities :: [(OccName, Fixity)]
mi_fixities = [(OccName, Fixity)]
fixities,
mi_warns :: Warnings
mi_warns = Warnings
warns,
mi_anns :: [IfaceAnnotation]
mi_anns = [IfaceAnnotation]
annotations,
mi_globals :: Maybe GlobalRdrEnv
mi_globals = GlobalRdrEnv -> Maybe GlobalRdrEnv
maybeGlobalRdrEnv GlobalRdrEnv
rdr_env,
mi_used_th :: Bool
mi_used_th = Bool
used_th,
mi_decls :: [IfaceDeclExts 'ModIfaceCore]
mi_decls = [IfaceDecl]
[IfaceDeclExts 'ModIfaceCore]
decls,
mi_hpc :: Bool
mi_hpc = HpcInfo -> Bool
isHpcUsed HpcInfo
hpc_info,
mi_trust :: IfaceTrustInfo
mi_trust = IfaceTrustInfo
trust_info,
mi_trust_pkg :: Bool
mi_trust_pkg = Bool
pkg_trust_req,
mi_complete_sigs :: [IfaceCompleteMatch]
mi_complete_sigs = [IfaceCompleteMatch]
icomplete_sigs,
mi_doc_hdr :: Maybe HsDocString
mi_doc_hdr = Maybe HsDocString
doc_hdr,
mi_decl_docs :: DeclDocMap
mi_decl_docs = DeclDocMap
decl_docs,
mi_arg_docs :: ArgDocMap
mi_arg_docs = ArgDocMap
arg_docs,
mi_final_exts :: IfaceBackendExts 'ModIfaceCore
mi_final_exts = () }
where
cmp_rule :: IfaceRule -> IfaceRule -> Ordering
cmp_rule = (IfaceRule -> RuleName) -> IfaceRule -> IfaceRule -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing IfaceRule -> RuleName
ifRuleName
cmp_inst :: IfaceClsInst -> IfaceClsInst -> Ordering
cmp_inst = (IfaceClsInst -> OccName)
-> IfaceClsInst -> IfaceClsInst -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Name -> OccName
nameOccName (Name -> OccName)
-> (IfaceClsInst -> Name) -> IfaceClsInst -> OccName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IfaceClsInst -> Name
ifDFun)
cmp_fam_inst :: IfaceFamInst -> IfaceFamInst -> Ordering
cmp_fam_inst = (IfaceFamInst -> OccName)
-> IfaceFamInst -> IfaceFamInst -> Ordering
forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Name -> OccName
nameOccName (Name -> OccName)
-> (IfaceFamInst -> Name) -> IfaceFamInst -> OccName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IfaceFamInst -> Name
ifFamInstTcName)
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
maybeGlobalRdrEnv :: GlobalRdrEnv -> Maybe GlobalRdrEnv
maybeGlobalRdrEnv :: GlobalRdrEnv -> Maybe GlobalRdrEnv
maybeGlobalRdrEnv GlobalRdrEnv
rdr_env
| HscTarget -> Bool
targetRetainsAllBindings (DynFlags -> HscTarget
hscTarget DynFlags
dflags) = GlobalRdrEnv -> Maybe GlobalRdrEnv
forall a. a -> Maybe a
Just GlobalRdrEnv
rdr_env
| Bool
otherwise = Maybe GlobalRdrEnv
forall a. Maybe a
Nothing
ifFamInstTcName :: IfaceFamInst -> Name
ifFamInstTcName = IfaceFamInst -> Name
ifFamInstFam
writeIfaceFile :: DynFlags -> FilePath -> ModIface -> IO ()
writeIfaceFile :: DynFlags -> String -> ModIface -> IO ()
writeIfaceFile DynFlags
dflags String
hi_file_path ModIface
new_iface
= do Bool -> String -> IO ()
createDirectoryIfMissing Bool
True (String -> String
takeDirectory String
hi_file_path)
DynFlags -> String -> ModIface -> IO ()
writeBinIface DynFlags
dflags String
hi_file_path ModIface
new_iface
mkHashFun
:: HscEnv
-> ExternalPackageState
-> (Name -> IO Fingerprint)
mkHashFun :: HscEnv -> ExternalPackageState -> Name -> IO Fingerprint
mkHashFun HscEnv
hsc_env ExternalPackageState
eps Name
name
| Module -> Bool
isHoleModule Module
orig_mod
= Module -> IO Fingerprint
lookup (UnitId -> ModuleName -> Module
mkModule (DynFlags -> UnitId
thisPackage DynFlags
dflags) (Module -> ModuleName
moduleName Module
orig_mod))
| Bool
otherwise
= Module -> IO Fingerprint
lookup Module
orig_mod
where
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
hpt :: HomePackageTable
hpt = HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env
pit :: PackageIfaceTable
pit = ExternalPackageState -> PackageIfaceTable
eps_PIT ExternalPackageState
eps
occ :: OccName
occ = Name -> OccName
nameOccName Name
name
orig_mod :: Module
orig_mod = HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
name
lookup :: Module -> IO Fingerprint
lookup Module
mod = do
MASSERT2( isExternalName name, ppr name )
ModIface
iface <- case HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
lookupIfaceByModule HomePackageTable
hpt PackageIfaceTable
pit Module
mod of
Just ModIface
iface -> ModIface -> IO ModIface
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
iface
Maybe ModIface
Nothing -> do
ModIface
iface <- HscEnv -> IfG ModIface -> IO ModIface
forall a. HscEnv -> IfG a -> IO a
initIfaceLoad HscEnv
hsc_env (IfG ModIface -> IO ModIface)
-> (TcRnIf IfGblEnv () (MaybeErr SDoc ModIface) -> IfG ModIface)
-> TcRnIf IfGblEnv () (MaybeErr SDoc ModIface)
-> IO ModIface
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcRnIf IfGblEnv () (MaybeErr SDoc ModIface) -> IfG ModIface
forall gbl lcl a.
TcRnIf gbl lcl (MaybeErr SDoc a) -> TcRnIf gbl lcl a
withException
(TcRnIf IfGblEnv () (MaybeErr SDoc ModIface) -> IO ModIface)
-> TcRnIf IfGblEnv () (MaybeErr SDoc ModIface) -> IO ModIface
forall a b. (a -> b) -> a -> b
$ SDoc
-> Module
-> WhereFrom
-> TcRnIf IfGblEnv () (MaybeErr SDoc ModIface)
forall lcl.
SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr SDoc ModIface)
loadInterface (String -> SDoc
text String
"lookupVers2") Module
mod WhereFrom
ImportBySystem
ModIface -> IO ModIface
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
iface
Fingerprint -> IO Fingerprint
forall (m :: * -> *) a. Monad m => a -> m a
return (Fingerprint -> IO Fingerprint) -> Fingerprint -> IO Fingerprint
forall a b. (a -> b) -> a -> b
$ (OccName, Fingerprint) -> Fingerprint
forall a b. (a, b) -> b
snd (ModIfaceBackend -> OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface) OccName
occ Maybe (OccName, Fingerprint)
-> (OccName, Fingerprint) -> (OccName, Fingerprint)
forall a. Maybe a -> a -> a
`orElse`
String -> SDoc -> (OccName, Fingerprint)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"lookupVers1" (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod SDoc -> SDoc -> SDoc
<+> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
occ))
addFingerprints
:: HscEnv
-> PartialModIface
-> IO ModIface
addFingerprints :: HscEnv -> PartialModIface -> IO ModIface
addFingerprints HscEnv
hsc_env PartialModIface
iface0
= do
ExternalPackageState
eps <- HscEnv -> IO ExternalPackageState
hscEPS HscEnv
hsc_env
let
decls :: [IfaceDeclExts 'ModIfaceCore]
decls = PartialModIface -> [IfaceDeclExts 'ModIfaceCore]
forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceDeclExts phase]
mi_decls PartialModIface
iface0
warn_fn :: OccName -> Maybe WarningTxt
warn_fn = Warnings -> OccName -> Maybe WarningTxt
mkIfaceWarnCache (PartialModIface -> Warnings
forall (phase :: ModIfacePhase). ModIface_ phase -> Warnings
mi_warns PartialModIface
iface0)
fix_fn :: OccName -> Maybe Fixity
fix_fn = [(OccName, Fixity)] -> OccName -> Maybe Fixity
mkIfaceFixCache (PartialModIface -> [(OccName, Fixity)]
forall (phase :: ModIfacePhase).
ModIface_ phase -> [(OccName, Fixity)]
mi_fixities PartialModIface
iface0)
declABI :: IfaceDecl -> IfaceDeclABI
declABI :: IfaceDecl -> IfaceDeclABI
declABI IfaceDecl
decl = (Module
this_mod, IfaceDecl
decl, IfaceDeclExtras
extras)
where extras :: IfaceDeclExtras
extras = (OccName -> Maybe Fixity)
-> (OccName -> [AnnPayload])
-> OccEnv [IfaceRule]
-> OccEnv [IfaceClsInst]
-> OccEnv [IfaceFamInst]
-> OccEnv Name
-> IfaceDecl
-> IfaceDeclExtras
declExtras OccName -> Maybe Fixity
fix_fn OccName -> [AnnPayload]
ann_fn OccEnv [IfaceRule]
non_orph_rules OccEnv [IfaceClsInst]
non_orph_insts
OccEnv [IfaceFamInst]
non_orph_fis OccEnv Name
top_lvl_name_env IfaceDecl
decl
top_lvl_name_env :: OccEnv Name
top_lvl_name_env =
[(OccName, Name)] -> OccEnv Name
forall a. [(OccName, a)] -> OccEnv a
mkOccEnv [ (Name -> OccName
nameOccName Name
nm, Name
nm)
| IfaceId { ifName :: IfaceDecl -> Name
ifName = Name
nm } <- [IfaceDecl]
decls ]
edges :: [ Node Unique IfaceDeclABI ]
edges :: [Node Unique IfaceDeclABI]
edges = [ IfaceDeclABI -> Unique -> [Unique] -> Node Unique IfaceDeclABI
forall key payload. payload -> key -> [key] -> Node key payload
DigraphNode IfaceDeclABI
abi (OccName -> Unique
forall a. Uniquable a => a -> Unique
getUnique (IfaceDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName IfaceDecl
decl)) [Unique]
out
| IfaceDecl
decl <- [IfaceDecl]
decls
, let abi :: IfaceDeclABI
abi = IfaceDecl -> IfaceDeclABI
declABI IfaceDecl
decl
, let out :: [Unique]
out = NameSet -> [Unique]
localOccs (NameSet -> [Unique]) -> NameSet -> [Unique]
forall a b. (a -> b) -> a -> b
$ IfaceDeclABI -> NameSet
freeNamesDeclABI IfaceDeclABI
abi
]
name_module :: Name -> Module
name_module Name
n = ASSERT2( isExternalName n, ppr n ) nameModule n
localOccs :: NameSet -> [Unique]
localOccs =
(Name -> Unique) -> [Name] -> [Unique]
forall a b. (a -> b) -> [a] -> [b]
map (OccName -> Unique
forall a. Uniquable a => a -> Unique
getUnique (OccName -> Unique) -> (Name -> OccName) -> Name -> Unique
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OccName -> OccName
getParent (OccName -> OccName) -> (Name -> OccName) -> Name -> OccName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> OccName
forall a. NamedThing a => a -> OccName
getOccName)
([Name] -> [Unique]) -> (NameSet -> [Name]) -> NameSet -> [Unique]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name -> Bool) -> [Name] -> [Name]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== Module
semantic_mod) (Module -> Bool) -> (Name -> Module) -> Name -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Module
name_module)
([Name] -> [Name]) -> (NameSet -> [Name]) -> NameSet -> [Name]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NameSet -> [Name]
forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet
where getParent :: OccName -> OccName
getParent :: OccName -> OccName
getParent OccName
occ = OccEnv OccName -> OccName -> Maybe OccName
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv OccName
parent_map OccName
occ Maybe OccName -> OccName -> OccName
forall a. Maybe a -> a -> a
`orElse` OccName
occ
parent_map :: OccEnv OccName
parent_map :: OccEnv OccName
parent_map = (OccEnv OccName -> IfaceDecl -> OccEnv OccName)
-> OccEnv OccName -> [IfaceDecl] -> OccEnv OccName
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' OccEnv OccName -> IfaceDecl -> OccEnv OccName
extend OccEnv OccName
forall a. OccEnv a
emptyOccEnv [IfaceDecl]
decls
where extend :: OccEnv OccName -> IfaceDecl -> OccEnv OccName
extend OccEnv OccName
env IfaceDecl
d =
OccEnv OccName -> [(OccName, OccName)] -> OccEnv OccName
forall a. OccEnv a -> [(OccName, a)] -> OccEnv a
extendOccEnvList OccEnv OccName
env [ (OccName
b,OccName
n) | OccName
b <- IfaceDecl -> [OccName]
ifaceDeclImplicitBndrs IfaceDecl
d ]
where n :: OccName
n = IfaceDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName IfaceDecl
d
groups :: [SCC IfaceDeclABI]
groups :: [SCC IfaceDeclABI]
groups = [Node Unique IfaceDeclABI] -> [SCC IfaceDeclABI]
forall key payload.
Uniquable key =>
[Node key payload] -> [SCC payload]
stronglyConnCompFromEdgedVerticesUniq [Node Unique IfaceDeclABI]
edges
global_hash_fn :: Name -> IO Fingerprint
global_hash_fn = HscEnv -> ExternalPackageState -> Name -> IO Fingerprint
mkHashFun HscEnv
hsc_env ExternalPackageState
eps
mk_put_name :: OccEnv (OccName,Fingerprint)
-> BinHandle -> Name -> IO ()
mk_put_name :: OccEnv (OccName, Fingerprint) -> BinHandle -> Name -> IO ()
mk_put_name OccEnv (OccName, Fingerprint)
local_env BinHandle
bh Name
name
| Name -> Bool
isWiredInName Name
name = BinHandle -> Name -> IO ()
putNameLiterally BinHandle
bh Name
name
| Bool
otherwise
= ASSERT2( isExternalName name, ppr name )
let hash :: IO Fingerprint
hash | HasDebugCallStack => Name -> Module
Name -> Module
nameModule Name
name Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
/= Module
semantic_mod = Name -> IO Fingerprint
global_hash_fn Name
name
| Module
semantic_mod Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
/= Module
this_mod
, Bool -> Bool
not (Module -> Bool
isHoleModule Module
semantic_mod) = Name -> IO Fingerprint
global_hash_fn Name
name
| Bool
otherwise = Fingerprint -> IO Fingerprint
forall (m :: * -> *) a. Monad m => a -> m a
return ((OccName, Fingerprint) -> Fingerprint
forall a b. (a, b) -> b
snd (OccEnv (OccName, Fingerprint)
-> OccName -> Maybe (OccName, Fingerprint)
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv (OccName, Fingerprint)
local_env (Name -> OccName
forall a. NamedThing a => a -> OccName
getOccName Name
name)
Maybe (OccName, Fingerprint)
-> (OccName, Fingerprint) -> (OccName, Fingerprint)
forall a. Maybe a -> a -> a
`orElse` String -> SDoc -> (OccName, Fingerprint)
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"urk! lookup local fingerprint"
(Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name SDoc -> SDoc -> SDoc
$$ OccEnv (OccName, Fingerprint) -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccEnv (OccName, Fingerprint)
local_env)))
in IO Fingerprint
hash IO Fingerprint -> (Fingerprint -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= BinHandle -> Fingerprint -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh
fingerprint_group :: (OccEnv (OccName,Fingerprint),
[(Fingerprint,IfaceDecl)])
-> SCC IfaceDeclABI
-> IO (OccEnv (OccName,Fingerprint),
[(Fingerprint,IfaceDecl)])
fingerprint_group :: (OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
-> SCC IfaceDeclABI
-> IO (OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
fingerprint_group (OccEnv (OccName, Fingerprint)
local_env, [(Fingerprint, IfaceDecl)]
decls_w_hashes) (AcyclicSCC IfaceDeclABI
abi)
= do let hash_fn :: BinHandle -> Name -> IO ()
hash_fn = OccEnv (OccName, Fingerprint) -> BinHandle -> Name -> IO ()
mk_put_name OccEnv (OccName, Fingerprint)
local_env
decl :: IfaceDecl
decl = IfaceDeclABI -> IfaceDecl
abiDecl IfaceDeclABI
abi
Fingerprint
hash <- (BinHandle -> Name -> IO ()) -> IfaceDeclABI -> IO Fingerprint
forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
hash_fn IfaceDeclABI
abi
OccEnv (OccName, Fingerprint)
env' <- OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> IO (OccEnv (OccName, Fingerprint))
extend_hash_env OccEnv (OccName, Fingerprint)
local_env (Fingerprint
hash,IfaceDecl
decl)
(OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
-> IO (OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
forall (m :: * -> *) a. Monad m => a -> m a
return (OccEnv (OccName, Fingerprint)
env', (Fingerprint
hash,IfaceDecl
decl) (Fingerprint, IfaceDecl)
-> [(Fingerprint, IfaceDecl)] -> [(Fingerprint, IfaceDecl)]
forall a. a -> [a] -> [a]
: [(Fingerprint, IfaceDecl)]
decls_w_hashes)
fingerprint_group (OccEnv (OccName, Fingerprint)
local_env, [(Fingerprint, IfaceDecl)]
decls_w_hashes) (CyclicSCC [IfaceDeclABI]
abis)
= do let decls :: [IfaceDecl]
decls = (IfaceDeclABI -> IfaceDecl) -> [IfaceDeclABI] -> [IfaceDecl]
forall a b. (a -> b) -> [a] -> [b]
map IfaceDeclABI -> IfaceDecl
abiDecl [IfaceDeclABI]
abis
OccEnv (OccName, Fingerprint)
local_env1 <- (OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> IO (OccEnv (OccName, Fingerprint)))
-> OccEnv (OccName, Fingerprint)
-> [(Fingerprint, IfaceDecl)]
-> IO (OccEnv (OccName, Fingerprint))
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> IO (OccEnv (OccName, Fingerprint))
extend_hash_env OccEnv (OccName, Fingerprint)
local_env
([Fingerprint] -> [IfaceDecl] -> [(Fingerprint, IfaceDecl)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Fingerprint -> [Fingerprint]
forall a. a -> [a]
repeat Fingerprint
fingerprint0) [IfaceDecl]
decls)
let hash_fn :: BinHandle -> Name -> IO ()
hash_fn = OccEnv (OccName, Fingerprint) -> BinHandle -> Name -> IO ()
mk_put_name OccEnv (OccName, Fingerprint)
local_env1
let stable_abis :: [IfaceDeclABI]
stable_abis = (IfaceDeclABI -> IfaceDeclABI -> Ordering)
-> [IfaceDeclABI] -> [IfaceDeclABI]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy IfaceDeclABI -> IfaceDeclABI -> Ordering
cmp_abiNames [IfaceDeclABI]
abis
Fingerprint
hash <- (BinHandle -> Name -> IO ()) -> [IfaceDeclABI] -> IO Fingerprint
forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
hash_fn [IfaceDeclABI]
stable_abis
let pairs :: [(Fingerprint, IfaceDecl)]
pairs = [Fingerprint] -> [IfaceDecl] -> [(Fingerprint, IfaceDecl)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Fingerprint -> [Fingerprint]
forall a. a -> [a]
repeat Fingerprint
hash) [IfaceDecl]
decls
OccEnv (OccName, Fingerprint)
local_env2 <- (OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> IO (OccEnv (OccName, Fingerprint)))
-> OccEnv (OccName, Fingerprint)
-> [(Fingerprint, IfaceDecl)]
-> IO (OccEnv (OccName, Fingerprint))
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> IO (OccEnv (OccName, Fingerprint))
extend_hash_env OccEnv (OccName, Fingerprint)
local_env [(Fingerprint, IfaceDecl)]
pairs
(OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
-> IO (OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
forall (m :: * -> *) a. Monad m => a -> m a
return (OccEnv (OccName, Fingerprint)
local_env2, [(Fingerprint, IfaceDecl)]
pairs [(Fingerprint, IfaceDecl)]
-> [(Fingerprint, IfaceDecl)] -> [(Fingerprint, IfaceDecl)]
forall a. [a] -> [a] -> [a]
++ [(Fingerprint, IfaceDecl)]
decls_w_hashes)
extend_hash_env :: OccEnv (OccName,Fingerprint)
-> (Fingerprint,IfaceDecl)
-> IO (OccEnv (OccName,Fingerprint))
extend_hash_env :: OccEnv (OccName, Fingerprint)
-> (Fingerprint, IfaceDecl) -> IO (OccEnv (OccName, Fingerprint))
extend_hash_env OccEnv (OccName, Fingerprint)
env0 (Fingerprint
hash,IfaceDecl
d) = do
OccEnv (OccName, Fingerprint) -> IO (OccEnv (OccName, Fingerprint))
forall (m :: * -> *) a. Monad m => a -> m a
return (((OccName, Fingerprint)
-> OccEnv (OccName, Fingerprint) -> OccEnv (OccName, Fingerprint))
-> OccEnv (OccName, Fingerprint)
-> [(OccName, Fingerprint)]
-> OccEnv (OccName, Fingerprint)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\(OccName
b,Fingerprint
fp) OccEnv (OccName, Fingerprint)
env -> OccEnv (OccName, Fingerprint)
-> OccName
-> (OccName, Fingerprint)
-> OccEnv (OccName, Fingerprint)
forall a. OccEnv a -> OccName -> a -> OccEnv a
extendOccEnv OccEnv (OccName, Fingerprint)
env OccName
b (OccName
b,Fingerprint
fp)) OccEnv (OccName, Fingerprint)
env0
(Fingerprint -> IfaceDecl -> [(OccName, Fingerprint)]
ifaceDeclFingerprints Fingerprint
hash IfaceDecl
d))
(OccEnv (OccName, Fingerprint)
local_env, [(Fingerprint, IfaceDecl)]
decls_w_hashes) <-
((OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
-> SCC IfaceDeclABI
-> IO (OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)]))
-> (OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
-> [SCC IfaceDeclABI]
-> IO (OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
-> SCC IfaceDeclABI
-> IO (OccEnv (OccName, Fingerprint), [(Fingerprint, IfaceDecl)])
fingerprint_group (OccEnv (OccName, Fingerprint)
forall a. OccEnv a
emptyOccEnv, []) [SCC IfaceDeclABI]
groups
let sorted_deps :: Dependencies
sorted_deps = Dependencies -> Dependencies
sortDependencies (PartialModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps PartialModIface
iface0)
let orph_mods :: [Module]
orph_mods
= (Module -> Bool) -> [Module] -> [Module]
forall a. (a -> Bool) -> [a] -> [a]
filter (Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
/= Module
this_mod)
([Module] -> [Module]) -> [Module] -> [Module]
forall a b. (a -> b) -> a -> b
$ Dependencies -> [Module]
dep_orphs Dependencies
sorted_deps
[Fingerprint]
dep_orphan_hashes <- HscEnv -> [Module] -> IO [Fingerprint]
getOrphanHashes HscEnv
hsc_env [Module]
orph_mods
Fingerprint
orphan_hash <- (BinHandle -> Name -> IO ())
-> ([Name], [IfaceRule], [IfaceFamInst]) -> IO Fingerprint
forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint (OccEnv (OccName, Fingerprint) -> BinHandle -> Name -> IO ()
mk_put_name OccEnv (OccName, Fingerprint)
local_env)
((IfaceClsInst -> Name) -> [IfaceClsInst] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map IfaceClsInst -> Name
ifDFun [IfaceClsInst]
orph_insts, [IfaceRule]
orph_rules, [IfaceFamInst]
orph_fis)
Fingerprint
export_hash <- (BinHandle -> Name -> IO ())
-> ([AvailInfo], Fingerprint, [Fingerprint],
[(InstalledUnitId, Bool)], [Module], IfaceTrustInfo)
-> IO Fingerprint
forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
putNameLiterally
(PartialModIface -> [AvailInfo]
forall (phase :: ModIfacePhase). ModIface_ phase -> [AvailInfo]
mi_exports PartialModIface
iface0,
Fingerprint
orphan_hash,
[Fingerprint]
dep_orphan_hashes,
Dependencies -> [(InstalledUnitId, Bool)]
dep_pkgs (PartialModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps PartialModIface
iface0),
Dependencies -> [Module]
dep_finsts (PartialModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps PartialModIface
iface0),
PartialModIface -> IfaceTrustInfo
forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust PartialModIface
iface0)
let sorted_decls :: [(Fingerprint, IfaceDecl)]
sorted_decls = Map OccName (Fingerprint, IfaceDecl) -> [(Fingerprint, IfaceDecl)]
forall k a. Map k a -> [a]
Map.elems (Map OccName (Fingerprint, IfaceDecl)
-> [(Fingerprint, IfaceDecl)])
-> Map OccName (Fingerprint, IfaceDecl)
-> [(Fingerprint, IfaceDecl)]
forall a b. (a -> b) -> a -> b
$ [(OccName, (Fingerprint, IfaceDecl))]
-> Map OccName (Fingerprint, IfaceDecl)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(OccName, (Fingerprint, IfaceDecl))]
-> Map OccName (Fingerprint, IfaceDecl))
-> [(OccName, (Fingerprint, IfaceDecl))]
-> Map OccName (Fingerprint, IfaceDecl)
forall a b. (a -> b) -> a -> b
$
[(IfaceDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName IfaceDecl
d, (Fingerprint, IfaceDecl)
e) | e :: (Fingerprint, IfaceDecl)
e@(Fingerprint
_, IfaceDecl
d) <- [(Fingerprint, IfaceDecl)]
decls_w_hashes]
Fingerprint
flag_hash <- DynFlags
-> Module -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintDynFlags DynFlags
dflags Module
this_mod BinHandle -> Name -> IO ()
putNameLiterally
Fingerprint
opt_hash <- DynFlags -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintOptFlags DynFlags
dflags BinHandle -> Name -> IO ()
putNameLiterally
Fingerprint
hpc_hash <- DynFlags -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintHpcFlags DynFlags
dflags BinHandle -> Name -> IO ()
putNameLiterally
Fingerprint
plugin_hash <- HscEnv -> IO Fingerprint
fingerprintPlugins HscEnv
hsc_env
Fingerprint
mod_hash <- (BinHandle -> Name -> IO ())
-> ([Fingerprint], Fingerprint, Warnings) -> IO Fingerprint
forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
putNameLiterally
(((Fingerprint, IfaceDecl) -> Fingerprint)
-> [(Fingerprint, IfaceDecl)] -> [Fingerprint]
forall a b. (a -> b) -> [a] -> [b]
map (Fingerprint, IfaceDecl) -> Fingerprint
forall a b. (a, b) -> a
fst [(Fingerprint, IfaceDecl)]
sorted_decls,
Fingerprint
export_hash,
PartialModIface -> Warnings
forall (phase :: ModIfacePhase). ModIface_ phase -> Warnings
mi_warns PartialModIface
iface0)
Fingerprint
iface_hash <- (BinHandle -> Name -> IO ())
-> (Fingerprint, [AnnPayload], [Usage], Dependencies, Bool)
-> IO Fingerprint
forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
putNameLiterally
(Fingerprint
mod_hash,
OccName -> [AnnPayload]
ann_fn (String -> OccName
mkVarOcc String
"module"),
PartialModIface -> [Usage]
forall (phase :: ModIfacePhase). ModIface_ phase -> [Usage]
mi_usages PartialModIface
iface0,
Dependencies
sorted_deps,
PartialModIface -> Bool
forall (phase :: ModIfacePhase). ModIface_ phase -> Bool
mi_hpc PartialModIface
iface0)
let
final_iface_exts :: ModIfaceBackend
final_iface_exts = ModIfaceBackend :: Fingerprint
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Fingerprint
-> Bool
-> Bool
-> Fingerprint
-> Fingerprint
-> (OccName -> Maybe WarningTxt)
-> (OccName -> Maybe Fixity)
-> (OccName -> Maybe (OccName, Fingerprint))
-> ModIfaceBackend
ModIfaceBackend
{ mi_iface_hash :: Fingerprint
mi_iface_hash = Fingerprint
iface_hash
, mi_mod_hash :: Fingerprint
mi_mod_hash = Fingerprint
mod_hash
, mi_flag_hash :: Fingerprint
mi_flag_hash = Fingerprint
flag_hash
, mi_opt_hash :: Fingerprint
mi_opt_hash = Fingerprint
opt_hash
, mi_hpc_hash :: Fingerprint
mi_hpc_hash = Fingerprint
hpc_hash
, mi_plugin_hash :: Fingerprint
mi_plugin_hash = Fingerprint
plugin_hash
, mi_orphan :: Bool
mi_orphan = Bool -> Bool
not ( (IfaceRule -> Bool) -> [IfaceRule] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all IfaceRule -> Bool
ifRuleAuto [IfaceRule]
orph_rules
Bool -> Bool -> Bool
&& [IfaceClsInst] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IfaceClsInst]
orph_insts
Bool -> Bool -> Bool
&& [IfaceFamInst] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IfaceFamInst]
orph_fis)
, mi_finsts :: Bool
mi_finsts = Bool -> Bool
not ([IfaceFamInst] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (PartialModIface -> [IfaceFamInst]
forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceFamInst]
mi_fam_insts PartialModIface
iface0))
, mi_exp_hash :: Fingerprint
mi_exp_hash = Fingerprint
export_hash
, mi_orphan_hash :: Fingerprint
mi_orphan_hash = Fingerprint
orphan_hash
, mi_warn_fn :: OccName -> Maybe WarningTxt
mi_warn_fn = OccName -> Maybe WarningTxt
warn_fn
, mi_fix_fn :: OccName -> Maybe Fixity
mi_fix_fn = OccName -> Maybe Fixity
fix_fn
, mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn = OccEnv (OccName, Fingerprint)
-> OccName -> Maybe (OccName, Fingerprint)
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv (OccName, Fingerprint)
local_env
}
final_iface :: ModIface
final_iface = PartialModIface
iface0 { mi_decls :: [IfaceDeclExts 'ModIfaceFinal]
mi_decls = [(Fingerprint, IfaceDecl)]
[IfaceDeclExts 'ModIfaceFinal]
sorted_decls, mi_final_exts :: IfaceBackendExts 'ModIfaceFinal
mi_final_exts = IfaceBackendExts 'ModIfaceFinal
ModIfaceBackend
final_iface_exts }
ModIface -> IO ModIface
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
final_iface
where
this_mod :: Module
this_mod = PartialModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module PartialModIface
iface0
semantic_mod :: Module
semantic_mod = PartialModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_semantic_module PartialModIface
iface0
dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
(OccEnv [IfaceClsInst]
non_orph_insts, [IfaceClsInst]
orph_insts) = (IfaceClsInst -> IsOrphan)
-> [IfaceClsInst] -> (OccEnv [IfaceClsInst], [IfaceClsInst])
forall decl.
(decl -> IsOrphan) -> [decl] -> (OccEnv [decl], [decl])
mkOrphMap IfaceClsInst -> IsOrphan
ifInstOrph (PartialModIface -> [IfaceClsInst]
forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceClsInst]
mi_insts PartialModIface
iface0)
(OccEnv [IfaceRule]
non_orph_rules, [IfaceRule]
orph_rules) = (IfaceRule -> IsOrphan)
-> [IfaceRule] -> (OccEnv [IfaceRule], [IfaceRule])
forall decl.
(decl -> IsOrphan) -> [decl] -> (OccEnv [decl], [decl])
mkOrphMap IfaceRule -> IsOrphan
ifRuleOrph (PartialModIface -> [IfaceRule]
forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceRule]
mi_rules PartialModIface
iface0)
(OccEnv [IfaceFamInst]
non_orph_fis, [IfaceFamInst]
orph_fis) = (IfaceFamInst -> IsOrphan)
-> [IfaceFamInst] -> (OccEnv [IfaceFamInst], [IfaceFamInst])
forall decl.
(decl -> IsOrphan) -> [decl] -> (OccEnv [decl], [decl])
mkOrphMap IfaceFamInst -> IsOrphan
ifFamInstOrph (PartialModIface -> [IfaceFamInst]
forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceFamInst]
mi_fam_insts PartialModIface
iface0)
ann_fn :: OccName -> [AnnPayload]
ann_fn = [IfaceAnnotation] -> OccName -> [AnnPayload]
mkIfaceAnnCache (PartialModIface -> [IfaceAnnotation]
forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceAnnotation]
mi_anns PartialModIface
iface0)
getOrphanHashes :: HscEnv -> [Module] -> IO [Fingerprint]
getOrphanHashes :: HscEnv -> [Module] -> IO [Fingerprint]
getOrphanHashes HscEnv
hsc_env [Module]
mods = do
ExternalPackageState
eps <- HscEnv -> IO ExternalPackageState
hscEPS HscEnv
hsc_env
let
hpt :: HomePackageTable
hpt = HscEnv -> HomePackageTable
hsc_HPT HscEnv
hsc_env
pit :: PackageIfaceTable
pit = ExternalPackageState -> PackageIfaceTable
eps_PIT ExternalPackageState
eps
get_orph_hash :: Module -> IO Fingerprint
get_orph_hash Module
mod =
case HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
lookupIfaceByModule HomePackageTable
hpt PackageIfaceTable
pit Module
mod of
Just ModIface
iface -> Fingerprint -> IO Fingerprint
forall (m :: * -> *) a. Monad m => a -> m a
return (ModIfaceBackend -> Fingerprint
mi_orphan_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface))
Maybe ModIface
Nothing -> do
ModIface
iface <- HscEnv -> IfG ModIface -> IO ModIface
forall a. HscEnv -> IfG a -> IO a
initIfaceLoad HscEnv
hsc_env (IfG ModIface -> IO ModIface)
-> (TcRnIf IfGblEnv () (MaybeErr SDoc ModIface) -> IfG ModIface)
-> TcRnIf IfGblEnv () (MaybeErr SDoc ModIface)
-> IO ModIface
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TcRnIf IfGblEnv () (MaybeErr SDoc ModIface) -> IfG ModIface
forall gbl lcl a.
TcRnIf gbl lcl (MaybeErr SDoc a) -> TcRnIf gbl lcl a
withException
(TcRnIf IfGblEnv () (MaybeErr SDoc ModIface) -> IO ModIface)
-> TcRnIf IfGblEnv () (MaybeErr SDoc ModIface) -> IO ModIface
forall a b. (a -> b) -> a -> b
$ SDoc
-> Module
-> WhereFrom
-> TcRnIf IfGblEnv () (MaybeErr SDoc ModIface)
forall lcl.
SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr SDoc ModIface)
loadInterface (String -> SDoc
text String
"getOrphanHashes") Module
mod WhereFrom
ImportBySystem
Fingerprint -> IO Fingerprint
forall (m :: * -> *) a. Monad m => a -> m a
return (ModIfaceBackend -> Fingerprint
mi_orphan_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface))
(Module -> IO Fingerprint) -> [Module] -> IO [Fingerprint]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Module -> IO Fingerprint
get_orph_hash [Module]
mods
sortDependencies :: Dependencies -> Dependencies
sortDependencies :: Dependencies -> Dependencies
sortDependencies Dependencies
d
= Deps :: [(ModuleName, Bool)]
-> [(InstalledUnitId, Bool)]
-> [Module]
-> [Module]
-> [ModuleName]
-> Dependencies
Deps { dep_mods :: [(ModuleName, Bool)]
dep_mods = ((ModuleName, Bool) -> (ModuleName, Bool) -> Ordering)
-> [(ModuleName, Bool)] -> [(ModuleName, Bool)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (RuleName -> RuleName -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (RuleName -> RuleName -> Ordering)
-> ((ModuleName, Bool) -> RuleName)
-> (ModuleName, Bool)
-> (ModuleName, Bool)
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (ModuleName -> RuleName
moduleNameFS(ModuleName -> RuleName)
-> ((ModuleName, Bool) -> ModuleName)
-> (ModuleName, Bool)
-> RuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(ModuleName, Bool) -> ModuleName
forall a b. (a, b) -> a
fst)) (Dependencies -> [(ModuleName, Bool)]
dep_mods Dependencies
d),
dep_pkgs :: [(InstalledUnitId, Bool)]
dep_pkgs = ((InstalledUnitId, Bool) -> (InstalledUnitId, Bool) -> Ordering)
-> [(InstalledUnitId, Bool)] -> [(InstalledUnitId, Bool)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (InstalledUnitId -> InstalledUnitId -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (InstalledUnitId -> InstalledUnitId -> Ordering)
-> ((InstalledUnitId, Bool) -> InstalledUnitId)
-> (InstalledUnitId, Bool)
-> (InstalledUnitId, Bool)
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (InstalledUnitId, Bool) -> InstalledUnitId
forall a b. (a, b) -> a
fst) (Dependencies -> [(InstalledUnitId, Bool)]
dep_pkgs Dependencies
d),
dep_orphs :: [Module]
dep_orphs = (Module -> Module -> Ordering) -> [Module] -> [Module]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Module -> Module -> Ordering
stableModuleCmp (Dependencies -> [Module]
dep_orphs Dependencies
d),
dep_finsts :: [Module]
dep_finsts = (Module -> Module -> Ordering) -> [Module] -> [Module]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Module -> Module -> Ordering
stableModuleCmp (Dependencies -> [Module]
dep_finsts Dependencies
d),
dep_plgins :: [ModuleName]
dep_plgins = (ModuleName -> ModuleName -> Ordering)
-> [ModuleName] -> [ModuleName]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (RuleName -> RuleName -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (RuleName -> RuleName -> Ordering)
-> (ModuleName -> RuleName) -> ModuleName -> ModuleName -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` ModuleName -> RuleName
moduleNameFS) (Dependencies -> [ModuleName]
dep_plgins Dependencies
d) }
mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload]
mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload]
mkIfaceAnnCache [IfaceAnnotation]
anns
= \OccName
n -> OccEnv [AnnPayload] -> OccName -> Maybe [AnnPayload]
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv [AnnPayload]
env OccName
n Maybe [AnnPayload] -> [AnnPayload] -> [AnnPayload]
forall a. Maybe a -> a -> a
`orElse` []
where
pair :: IfaceAnnotation -> (OccName, [AnnPayload])
pair (IfaceAnnotation IfaceAnnTarget
target AnnPayload
value) =
(case IfaceAnnTarget
target of
NamedTarget OccName
occn -> OccName
occn
ModuleTarget Module
_ -> String -> OccName
mkVarOcc String
"module"
, [AnnPayload
value])
env :: OccEnv [AnnPayload]
env = ([AnnPayload] -> [AnnPayload] -> [AnnPayload])
-> [(OccName, [AnnPayload])] -> OccEnv [AnnPayload]
forall a. (a -> a -> a) -> [(OccName, a)] -> OccEnv a
mkOccEnv_C (([AnnPayload] -> [AnnPayload] -> [AnnPayload])
-> [AnnPayload] -> [AnnPayload] -> [AnnPayload]
forall a b c. (a -> b -> c) -> b -> a -> c
flip [AnnPayload] -> [AnnPayload] -> [AnnPayload]
forall a. [a] -> [a] -> [a]
(++)) ((IfaceAnnotation -> (OccName, [AnnPayload]))
-> [IfaceAnnotation] -> [(OccName, [AnnPayload])]
forall a b. (a -> b) -> [a] -> [b]
map IfaceAnnotation -> (OccName, [AnnPayload])
pair [IfaceAnnotation]
anns)
type IfaceDeclABI = (Module, IfaceDecl, IfaceDeclExtras)
data
= IfaceIdExtras
|
(Maybe Fixity)
[IfaceInstABI]
[AnnPayload]
[IfaceIdExtras]
|
(Maybe Fixity)
[IfaceInstABI]
[AnnPayload]
[IfaceIdExtras]
[IfExtName]
| (Maybe Fixity) [AnnPayload]
| (Maybe Fixity) [IfaceInstABI] [AnnPayload]
|
data
=
(Maybe Fixity)
[IfaceRule]
[AnnPayload]
type IfaceInstABI = IfExtName
abiDecl :: IfaceDeclABI -> IfaceDecl
abiDecl :: IfaceDeclABI -> IfaceDecl
abiDecl (Module
_, IfaceDecl
decl, IfaceDeclExtras
_) = IfaceDecl
decl
cmp_abiNames :: IfaceDeclABI -> IfaceDeclABI -> Ordering
cmp_abiNames :: IfaceDeclABI -> IfaceDeclABI -> Ordering
cmp_abiNames IfaceDeclABI
abi1 IfaceDeclABI
abi2 = IfaceDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName (IfaceDeclABI -> IfaceDecl
abiDecl IfaceDeclABI
abi1) OccName -> OccName -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare`
IfaceDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName (IfaceDeclABI -> IfaceDecl
abiDecl IfaceDeclABI
abi2)
freeNamesDeclABI :: IfaceDeclABI -> NameSet
freeNamesDeclABI :: IfaceDeclABI -> NameSet
freeNamesDeclABI (Module
_mod, IfaceDecl
decl, IfaceDeclExtras
extras) =
IfaceDecl -> NameSet
freeNamesIfDecl IfaceDecl
decl NameSet -> NameSet -> NameSet
`unionNameSet` IfaceDeclExtras -> NameSet
freeNamesDeclExtras IfaceDeclExtras
extras
freeNamesDeclExtras :: IfaceDeclExtras -> NameSet
(IfaceIdExtras IfaceIdExtras
id_extras)
= IfaceIdExtras -> NameSet
freeNamesIdExtras IfaceIdExtras
id_extras
freeNamesDeclExtras (IfaceDataExtras Maybe Fixity
_ [Name]
insts [AnnPayload]
_ [IfaceIdExtras]
subs)
= [NameSet] -> NameSet
unionNameSets ([Name] -> NameSet
mkNameSet [Name]
insts NameSet -> [NameSet] -> [NameSet]
forall a. a -> [a] -> [a]
: (IfaceIdExtras -> NameSet) -> [IfaceIdExtras] -> [NameSet]
forall a b. (a -> b) -> [a] -> [b]
map IfaceIdExtras -> NameSet
freeNamesIdExtras [IfaceIdExtras]
subs)
freeNamesDeclExtras (IfaceClassExtras Maybe Fixity
_ [Name]
insts [AnnPayload]
_ [IfaceIdExtras]
subs [Name]
defms)
= [NameSet] -> NameSet
unionNameSets ([NameSet] -> NameSet) -> [NameSet] -> NameSet
forall a b. (a -> b) -> a -> b
$
[Name] -> NameSet
mkNameSet [Name]
insts NameSet -> [NameSet] -> [NameSet]
forall a. a -> [a] -> [a]
: [Name] -> NameSet
mkNameSet [Name]
defms NameSet -> [NameSet] -> [NameSet]
forall a. a -> [a] -> [a]
: (IfaceIdExtras -> NameSet) -> [IfaceIdExtras] -> [NameSet]
forall a b. (a -> b) -> [a] -> [b]
map IfaceIdExtras -> NameSet
freeNamesIdExtras [IfaceIdExtras]
subs
freeNamesDeclExtras (IfaceSynonymExtras Maybe Fixity
_ [AnnPayload]
_)
= NameSet
emptyNameSet
freeNamesDeclExtras (IfaceFamilyExtras Maybe Fixity
_ [Name]
insts [AnnPayload]
_)
= [Name] -> NameSet
mkNameSet [Name]
insts
freeNamesDeclExtras IfaceDeclExtras
IfaceOtherDeclExtras
= NameSet
emptyNameSet
freeNamesIdExtras :: IfaceIdExtras -> NameSet
(IdExtras Maybe Fixity
_ [IfaceRule]
rules [AnnPayload]
_) = [NameSet] -> NameSet
unionNameSets ((IfaceRule -> NameSet) -> [IfaceRule] -> [NameSet]
forall a b. (a -> b) -> [a] -> [b]
map IfaceRule -> NameSet
freeNamesIfRule [IfaceRule]
rules)
instance Outputable IfaceDeclExtras where
ppr :: IfaceDeclExtras -> SDoc
ppr IfaceDeclExtras
IfaceOtherDeclExtras = SDoc
Outputable.empty
ppr (IfaceIdExtras IfaceIdExtras
extras) = IfaceIdExtras -> SDoc
ppr_id_extras IfaceIdExtras
extras
ppr (IfaceSynonymExtras Maybe Fixity
fix [AnnPayload]
anns) = [SDoc] -> SDoc
vcat [Maybe Fixity -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix, [AnnPayload] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [AnnPayload]
anns]
ppr (IfaceFamilyExtras Maybe Fixity
fix [Name]
finsts [AnnPayload]
anns) = [SDoc] -> SDoc
vcat [Maybe Fixity -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix, [Name] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Name]
finsts, [AnnPayload] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [AnnPayload]
anns]
ppr (IfaceDataExtras Maybe Fixity
fix [Name]
insts [AnnPayload]
anns [IfaceIdExtras]
stuff) = [SDoc] -> SDoc
vcat [Maybe Fixity -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix, [Name] -> SDoc
ppr_insts [Name]
insts, [AnnPayload] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [AnnPayload]
anns,
[IfaceIdExtras] -> SDoc
ppr_id_extras_s [IfaceIdExtras]
stuff]
ppr (IfaceClassExtras Maybe Fixity
fix [Name]
insts [AnnPayload]
anns [IfaceIdExtras]
stuff [Name]
defms) =
[SDoc] -> SDoc
vcat [Maybe Fixity -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix, [Name] -> SDoc
ppr_insts [Name]
insts, [AnnPayload] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [AnnPayload]
anns,
[IfaceIdExtras] -> SDoc
ppr_id_extras_s [IfaceIdExtras]
stuff, [Name] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Name]
defms]
ppr_insts :: [IfaceInstABI] -> SDoc
ppr_insts :: [Name] -> SDoc
ppr_insts [Name]
_ = String -> SDoc
text String
"<insts>"
ppr_id_extras_s :: [IfaceIdExtras] -> SDoc
[IfaceIdExtras]
stuff = [SDoc] -> SDoc
vcat ((IfaceIdExtras -> SDoc) -> [IfaceIdExtras] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceIdExtras -> SDoc
ppr_id_extras [IfaceIdExtras]
stuff)
ppr_id_extras :: IfaceIdExtras -> SDoc
(IdExtras Maybe Fixity
fix [IfaceRule]
rules [AnnPayload]
anns) = Maybe Fixity -> SDoc
forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
vcat ((IfaceRule -> SDoc) -> [IfaceRule] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map IfaceRule -> SDoc
forall a. Outputable a => a -> SDoc
ppr [IfaceRule]
rules) SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
vcat ((AnnPayload -> SDoc) -> [AnnPayload] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map AnnPayload -> SDoc
forall a. Outputable a => a -> SDoc
ppr [AnnPayload]
anns)
instance Binary IfaceDeclExtras where
get :: BinHandle -> IO IfaceDeclExtras
get BinHandle
_bh = String -> IO IfaceDeclExtras
forall a. String -> a
panic String
"no get for IfaceDeclExtras"
put_ :: BinHandle -> IfaceDeclExtras -> IO ()
put_ BinHandle
bh (IfaceIdExtras IfaceIdExtras
extras) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1; BinHandle -> IfaceIdExtras -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh IfaceIdExtras
extras
put_ BinHandle
bh (IfaceDataExtras Maybe Fixity
fix [Name]
insts [AnnPayload]
anns [IfaceIdExtras]
cons) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2; BinHandle -> Maybe Fixity -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix; BinHandle -> [Name] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Name]
insts; BinHandle -> [AnnPayload] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [AnnPayload]
anns; BinHandle -> [IfaceIdExtras] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceIdExtras]
cons
put_ BinHandle
bh (IfaceClassExtras Maybe Fixity
fix [Name]
insts [AnnPayload]
anns [IfaceIdExtras]
methods [Name]
defms) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3
BinHandle -> Maybe Fixity -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix
BinHandle -> [Name] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Name]
insts
BinHandle -> [AnnPayload] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [AnnPayload]
anns
BinHandle -> [IfaceIdExtras] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceIdExtras]
methods
BinHandle -> [Name] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Name]
defms
put_ BinHandle
bh (IfaceSynonymExtras Maybe Fixity
fix [AnnPayload]
anns) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4; BinHandle -> Maybe Fixity -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix; BinHandle -> [AnnPayload] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [AnnPayload]
anns
put_ BinHandle
bh (IfaceFamilyExtras Maybe Fixity
fix [Name]
finsts [AnnPayload]
anns) = do
BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5; BinHandle -> Maybe Fixity -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix; BinHandle -> [Name] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Name]
finsts; BinHandle -> [AnnPayload] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [AnnPayload]
anns
put_ BinHandle
bh IfaceDeclExtras
IfaceOtherDeclExtras = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
6
instance Binary IfaceIdExtras where
get :: BinHandle -> IO IfaceIdExtras
get BinHandle
_bh = String -> IO IfaceIdExtras
forall a. String -> a
panic String
"no get for IfaceIdExtras"
put_ :: BinHandle -> IfaceIdExtras -> IO ()
put_ BinHandle
bh (IdExtras Maybe Fixity
fix [IfaceRule]
rules [AnnPayload]
anns)= do { BinHandle -> Maybe Fixity -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix; BinHandle -> [IfaceRule] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceRule]
rules; BinHandle -> [AnnPayload] -> IO ()
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [AnnPayload]
anns }
declExtras :: (OccName -> Maybe Fixity)
-> (OccName -> [AnnPayload])
-> OccEnv [IfaceRule]
-> OccEnv [IfaceClsInst]
-> OccEnv [IfaceFamInst]
-> OccEnv IfExtName
-> IfaceDecl
-> IfaceDeclExtras
OccName -> Maybe Fixity
fix_fn OccName -> [AnnPayload]
ann_fn OccEnv [IfaceRule]
rule_env OccEnv [IfaceClsInst]
inst_env OccEnv [IfaceFamInst]
fi_env OccEnv Name
dm_env IfaceDecl
decl
= case IfaceDecl
decl of
IfaceId{} -> IfaceIdExtras -> IfaceDeclExtras
IfaceIdExtras (OccName -> IfaceIdExtras
id_extras OccName
n)
IfaceData{ifCons :: IfaceDecl -> IfaceConDecls
ifCons=IfaceConDecls
cons} ->
Maybe Fixity
-> [Name] -> [AnnPayload] -> [IfaceIdExtras] -> IfaceDeclExtras
IfaceDataExtras (OccName -> Maybe Fixity
fix_fn OccName
n)
((IfaceFamInst -> Name) -> [IfaceFamInst] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map IfaceFamInst -> Name
ifFamInstAxiom (OccEnv [IfaceFamInst] -> OccName -> [IfaceFamInst]
forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceFamInst]
fi_env OccName
n) [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++
(IfaceClsInst -> Name) -> [IfaceClsInst] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map IfaceClsInst -> Name
ifDFun (OccEnv [IfaceClsInst] -> OccName -> [IfaceClsInst]
forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceClsInst]
inst_env OccName
n))
(OccName -> [AnnPayload]
ann_fn OccName
n)
((IfaceConDecl -> IfaceIdExtras)
-> [IfaceConDecl] -> [IfaceIdExtras]
forall a b. (a -> b) -> [a] -> [b]
map (OccName -> IfaceIdExtras
id_extras (OccName -> IfaceIdExtras)
-> (IfaceConDecl -> OccName) -> IfaceConDecl -> IfaceIdExtras
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> OccName
forall name. HasOccName name => name -> OccName
occName (Name -> OccName)
-> (IfaceConDecl -> Name) -> IfaceConDecl -> OccName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IfaceConDecl -> Name
ifConName) (IfaceConDecls -> [IfaceConDecl]
visibleIfConDecls IfaceConDecls
cons))
IfaceClass{ifBody :: IfaceDecl -> IfaceClassBody
ifBody = IfConcreteClass { ifSigs :: IfaceClassBody -> [IfaceClassOp]
ifSigs=[IfaceClassOp]
sigs, ifATs :: IfaceClassBody -> [IfaceAT]
ifATs=[IfaceAT]
ats }} ->
Maybe Fixity
-> [Name]
-> [AnnPayload]
-> [IfaceIdExtras]
-> [Name]
-> IfaceDeclExtras
IfaceClassExtras (OccName -> Maybe Fixity
fix_fn OccName
n) [Name]
insts (OccName -> [AnnPayload]
ann_fn OccName
n) [IfaceIdExtras]
meths [Name]
defms
where
insts :: [Name]
insts = ((IfaceClsInst -> Name) -> [IfaceClsInst] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map IfaceClsInst -> Name
ifDFun ([IfaceClsInst] -> [Name]) -> [IfaceClsInst] -> [Name]
forall a b. (a -> b) -> a -> b
$ ((IfaceAT -> [IfaceClsInst]) -> [IfaceAT] -> [IfaceClsInst]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap IfaceAT -> [IfaceClsInst]
at_extras [IfaceAT]
ats)
[IfaceClsInst] -> [IfaceClsInst] -> [IfaceClsInst]
forall a. [a] -> [a] -> [a]
++ OccEnv [IfaceClsInst] -> OccName -> [IfaceClsInst]
forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceClsInst]
inst_env OccName
n)
meths :: [IfaceIdExtras]
meths = [OccName -> IfaceIdExtras
id_extras (Name -> OccName
forall a. NamedThing a => a -> OccName
getOccName Name
op) | IfaceClassOp Name
op IfaceType
_ Maybe (DefMethSpec IfaceType)
_ <- [IfaceClassOp]
sigs]
defms :: [Name]
defms = [ Name
dmName
| IfaceClassOp Name
bndr IfaceType
_ (Just DefMethSpec IfaceType
_) <- [IfaceClassOp]
sigs
, let dmOcc :: OccName
dmOcc = OccName -> OccName
mkDefaultMethodOcc (Name -> OccName
nameOccName Name
bndr)
, Just Name
dmName <- [OccEnv Name -> OccName -> Maybe Name
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv Name
dm_env OccName
dmOcc] ]
IfaceSynonym{} -> Maybe Fixity -> [AnnPayload] -> IfaceDeclExtras
IfaceSynonymExtras (OccName -> Maybe Fixity
fix_fn OccName
n)
(OccName -> [AnnPayload]
ann_fn OccName
n)
IfaceFamily{} -> Maybe Fixity -> [Name] -> [AnnPayload] -> IfaceDeclExtras
IfaceFamilyExtras (OccName -> Maybe Fixity
fix_fn OccName
n)
((IfaceFamInst -> Name) -> [IfaceFamInst] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map IfaceFamInst -> Name
ifFamInstAxiom (OccEnv [IfaceFamInst] -> OccName -> [IfaceFamInst]
forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceFamInst]
fi_env OccName
n))
(OccName -> [AnnPayload]
ann_fn OccName
n)
IfaceDecl
_other -> IfaceDeclExtras
IfaceOtherDeclExtras
where
n :: OccName
n = IfaceDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName IfaceDecl
decl
id_extras :: OccName -> IfaceIdExtras
id_extras OccName
occ = Maybe Fixity -> [IfaceRule] -> [AnnPayload] -> IfaceIdExtras
IdExtras (OccName -> Maybe Fixity
fix_fn OccName
occ) (OccEnv [IfaceRule] -> OccName -> [IfaceRule]
forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceRule]
rule_env OccName
occ) (OccName -> [AnnPayload]
ann_fn OccName
occ)
at_extras :: IfaceAT -> [IfaceClsInst]
at_extras (IfaceAT IfaceDecl
decl Maybe IfaceType
_) = OccEnv [IfaceClsInst] -> OccName -> [IfaceClsInst]
forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceClsInst]
inst_env (IfaceDecl -> OccName
forall a. NamedThing a => a -> OccName
getOccName IfaceDecl
decl)
lookupOccEnvL :: OccEnv [v] -> OccName -> [v]
lookupOccEnvL :: OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [v]
env OccName
k = OccEnv [v] -> OccName -> Maybe [v]
forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv [v]
env OccName
k Maybe [v] -> [v] -> [v]
forall a. Maybe a -> a -> a
`orElse` []
mkOrphMap :: (decl -> IsOrphan)
-> [decl]
-> (OccEnv [decl],
[decl])
mkOrphMap :: (decl -> IsOrphan) -> [decl] -> (OccEnv [decl], [decl])
mkOrphMap decl -> IsOrphan
get_key [decl]
decls
= ((OccEnv [decl], [decl]) -> decl -> (OccEnv [decl], [decl]))
-> (OccEnv [decl], [decl]) -> [decl] -> (OccEnv [decl], [decl])
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (OccEnv [decl], [decl]) -> decl -> (OccEnv [decl], [decl])
go (OccEnv [decl]
forall a. OccEnv a
emptyOccEnv, []) [decl]
decls
where
go :: (OccEnv [decl], [decl]) -> decl -> (OccEnv [decl], [decl])
go (OccEnv [decl]
non_orphs, [decl]
orphs) decl
d
| NotOrphan OccName
occ <- decl -> IsOrphan
get_key decl
d
= ((decl -> [decl] -> [decl])
-> (decl -> [decl])
-> OccEnv [decl]
-> OccName
-> decl
-> OccEnv [decl]
forall a b.
(a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
extendOccEnv_Acc (:) decl -> [decl]
forall a. a -> [a]
singleton OccEnv [decl]
non_orphs OccName
occ decl
d, [decl]
orphs)
| Bool
otherwise = (OccEnv [decl]
non_orphs, decl
ddecl -> [decl] -> [decl]
forall a. a -> [a] -> [a]
:[decl]
orphs)
mkIfaceCompleteSig :: CompleteMatch -> IfaceCompleteMatch
mkIfaceCompleteSig :: CompleteMatch -> IfaceCompleteMatch
mkIfaceCompleteSig (CompleteMatch [Name]
cls Name
tc) = [Name] -> Name -> IfaceCompleteMatch
IfaceCompleteMatch [Name]
cls Name
tc
mkIfaceAnnotation :: Annotation -> IfaceAnnotation
mkIfaceAnnotation :: Annotation -> IfaceAnnotation
mkIfaceAnnotation (Annotation { ann_target :: Annotation -> CoreAnnTarget
ann_target = CoreAnnTarget
target, ann_value :: Annotation -> AnnPayload
ann_value = AnnPayload
payload })
= IfaceAnnotation :: IfaceAnnTarget -> AnnPayload -> IfaceAnnotation
IfaceAnnotation {
ifAnnotatedTarget :: IfaceAnnTarget
ifAnnotatedTarget = (Name -> OccName) -> CoreAnnTarget -> IfaceAnnTarget
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Name -> OccName
nameOccName CoreAnnTarget
target,
ifAnnotatedValue :: AnnPayload
ifAnnotatedValue = AnnPayload
payload
}
mkIfaceExports :: [AvailInfo] -> [IfaceExport]
mkIfaceExports :: [AvailInfo] -> [AvailInfo]
mkIfaceExports [AvailInfo]
exports
= (AvailInfo -> AvailInfo -> Ordering) -> [AvailInfo] -> [AvailInfo]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy AvailInfo -> AvailInfo -> Ordering
stableAvailCmp ((AvailInfo -> AvailInfo) -> [AvailInfo] -> [AvailInfo]
forall a b. (a -> b) -> [a] -> [b]
map AvailInfo -> AvailInfo
sort_subs [AvailInfo]
exports)
where
sort_subs :: AvailInfo -> AvailInfo
sort_subs :: AvailInfo -> AvailInfo
sort_subs (Avail Name
n) = Name -> AvailInfo
Avail Name
n
sort_subs (AvailTC Name
n [] [FieldLabel]
fs) = Name -> [Name] -> [FieldLabel] -> AvailInfo
AvailTC Name
n [] ([FieldLabel] -> [FieldLabel]
sort_flds [FieldLabel]
fs)
sort_subs (AvailTC Name
n (Name
m:[Name]
ms) [FieldLabel]
fs)
| Name
nName -> Name -> Bool
forall a. Eq a => a -> a -> Bool
==Name
m = Name -> [Name] -> [FieldLabel] -> AvailInfo
AvailTC Name
n (Name
mName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:(Name -> Name -> Ordering) -> [Name] -> [Name]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Name -> Name -> Ordering
stableNameCmp [Name]
ms) ([FieldLabel] -> [FieldLabel]
sort_flds [FieldLabel]
fs)
| Bool
otherwise = Name -> [Name] -> [FieldLabel] -> AvailInfo
AvailTC Name
n ((Name -> Name -> Ordering) -> [Name] -> [Name]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Name -> Name -> Ordering
stableNameCmp (Name
mName -> [Name] -> [Name]
forall a. a -> [a] -> [a]
:[Name]
ms)) ([FieldLabel] -> [FieldLabel]
sort_flds [FieldLabel]
fs)
sort_flds :: [FieldLabel] -> [FieldLabel]
sort_flds = (FieldLabel -> FieldLabel -> Ordering)
-> [FieldLabel] -> [FieldLabel]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (Name -> Name -> Ordering
stableNameCmp (Name -> Name -> Ordering)
-> (FieldLabel -> Name) -> FieldLabel -> FieldLabel -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` FieldLabel -> Name
forall a. FieldLbl a -> a
flSelector)
data RecompileRequired
= UpToDate
| MustCompile
| RecompBecause String
deriving RecompileRequired -> RecompileRequired -> Bool
(RecompileRequired -> RecompileRequired -> Bool)
-> (RecompileRequired -> RecompileRequired -> Bool)
-> Eq RecompileRequired
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecompileRequired -> RecompileRequired -> Bool
$c/= :: RecompileRequired -> RecompileRequired -> Bool
== :: RecompileRequired -> RecompileRequired -> Bool
$c== :: RecompileRequired -> RecompileRequired -> Bool
Eq
instance Semigroup RecompileRequired where
RecompileRequired
UpToDate <> :: RecompileRequired -> RecompileRequired -> RecompileRequired
<> RecompileRequired
r = RecompileRequired
r
RecompileRequired
mc <> RecompileRequired
_ = RecompileRequired
mc
instance Monoid RecompileRequired where
mempty :: RecompileRequired
mempty = RecompileRequired
UpToDate
recompileRequired :: RecompileRequired -> Bool
recompileRequired :: RecompileRequired -> Bool
recompileRequired RecompileRequired
UpToDate = Bool
False
recompileRequired RecompileRequired
_ = Bool
True
checkOldIface
:: HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> IO (RecompileRequired, Maybe ModIface)
checkOldIface :: HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> IO (RecompileRequired, Maybe ModIface)
checkOldIface HscEnv
hsc_env ModSummary
mod_summary SourceModified
source_modified Maybe ModIface
maybe_iface
= do let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
DynFlags -> String -> IO ()
showPass DynFlags
dflags (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
String
"Checking old interface for " String -> String -> String
forall a. [a] -> [a] -> [a]
++
(DynFlags -> Module -> String
forall a. Outputable a => DynFlags -> a -> String
showPpr DynFlags
dflags (Module -> String) -> Module -> String
forall a b. (a -> b) -> a -> b
$ ModSummary -> Module
ms_mod ModSummary
mod_summary) String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" (use -ddump-hi-diffs for more details)"
SDoc
-> HscEnv
-> IfG (RecompileRequired, Maybe ModIface)
-> IO (RecompileRequired, Maybe ModIface)
forall a. SDoc -> HscEnv -> IfG a -> IO a
initIfaceCheck (String -> SDoc
text String
"checkOldIface") HscEnv
hsc_env (IfG (RecompileRequired, Maybe ModIface)
-> IO (RecompileRequired, Maybe ModIface))
-> IfG (RecompileRequired, Maybe ModIface)
-> IO (RecompileRequired, Maybe ModIface)
forall a b. (a -> b) -> a -> b
$
HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> IfG (RecompileRequired, Maybe ModIface)
check_old_iface HscEnv
hsc_env ModSummary
mod_summary SourceModified
source_modified Maybe ModIface
maybe_iface
check_old_iface
:: HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> IfG (RecompileRequired, Maybe ModIface)
check_old_iface :: HscEnv
-> ModSummary
-> SourceModified
-> Maybe ModIface
-> IfG (RecompileRequired, Maybe ModIface)
check_old_iface HscEnv
hsc_env ModSummary
mod_summary SourceModified
src_modified Maybe ModIface
maybe_iface
= let dflags :: DynFlags
dflags = HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env
getIface :: IOEnv (Env m n) (Maybe ModIface)
getIface =
case Maybe ModIface
maybe_iface of
Just ModIface
_ -> do
SDoc -> TcRnIf m n ()
forall m n. SDoc -> TcRnIf m n ()
traceIf (String -> SDoc
text String
"We already have the old interface for" SDoc -> SDoc -> SDoc
<+>
Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModSummary -> Module
ms_mod ModSummary
mod_summary))
Maybe ModIface -> IOEnv (Env m n) (Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ModIface
maybe_iface
Maybe ModIface
Nothing -> IOEnv (Env m n) (Maybe ModIface)
forall gbl lcl. IOEnv (Env gbl lcl) (Maybe ModIface)
loadIface
loadIface :: IOEnv (Env gbl lcl) (Maybe ModIface)
loadIface = do
let iface_path :: String
iface_path = ModSummary -> String
msHiFilePath ModSummary
mod_summary
MaybeErr SDoc ModIface
read_result <- Module -> String -> TcRnIf gbl lcl (MaybeErr SDoc ModIface)
forall gbl lcl.
Module -> String -> TcRnIf gbl lcl (MaybeErr SDoc ModIface)
readIface (ModSummary -> Module
ms_mod ModSummary
mod_summary) String
iface_path
case MaybeErr SDoc ModIface
read_result of
Failed SDoc
err -> do
SDoc -> TcRnIf gbl lcl ()
forall m n. SDoc -> TcRnIf m n ()
traceIf (String -> SDoc
text String
"FYI: cannot read old interface file:" SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest Int
4 SDoc
err)
SDoc -> TcRnIf gbl lcl ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (String -> SDoc
text String
"Old interface file was invalid:" SDoc -> SDoc -> SDoc
$$ Int -> SDoc -> SDoc
nest Int
4 SDoc
err)
Maybe ModIface -> IOEnv (Env gbl lcl) (Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ModIface
forall a. Maybe a
Nothing
Succeeded ModIface
iface -> do
SDoc -> TcRnIf gbl lcl ()
forall m n. SDoc -> TcRnIf m n ()
traceIf (String -> SDoc
text String
"Read the interface file" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
iface_path)
Maybe ModIface -> IOEnv (Env gbl lcl) (Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ModIface -> IOEnv (Env gbl lcl) (Maybe ModIface))
-> Maybe ModIface -> IOEnv (Env gbl lcl) (Maybe ModIface)
forall a b. (a -> b) -> a -> b
$ ModIface -> Maybe ModIface
forall a. a -> Maybe a
Just ModIface
iface
src_changed :: Bool
src_changed
| GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_ForceRecomp (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env) = Bool
True
| SourceModified
SourceModified <- SourceModified
src_modified = Bool
True
| Bool
otherwise = Bool
False
in do
Bool -> IOEnv (Env IfGblEnv ()) () -> IOEnv (Env IfGblEnv ()) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
src_changed (IOEnv (Env IfGblEnv ()) () -> IOEnv (Env IfGblEnv ()) ())
-> IOEnv (Env IfGblEnv ()) () -> IOEnv (Env IfGblEnv ()) ()
forall a b. (a -> b) -> a -> b
$
SDoc -> IOEnv (Env IfGblEnv ()) ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (Int -> SDoc -> SDoc
nest Int
4 (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"Source file changed or recompilation check turned off")
case Bool
src_changed of
Bool
True | Bool -> Bool
not (HscTarget -> Bool
isObjectTarget (HscTarget -> Bool) -> HscTarget -> Bool
forall a b. (a -> b) -> a -> b
$ DynFlags -> HscTarget
hscTarget DynFlags
dflags) ->
(RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
MustCompile, Maybe ModIface
maybe_iface)
Bool
True -> do
Maybe ModIface
maybe_iface' <- IOEnv (Env IfGblEnv ()) (Maybe ModIface)
forall gbl lcl. IOEnv (Env gbl lcl) (Maybe ModIface)
getIface
(RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
MustCompile, Maybe ModIface
maybe_iface')
Bool
False -> do
Maybe ModIface
maybe_iface' <- IOEnv (Env IfGblEnv ()) (Maybe ModIface)
forall gbl lcl. IOEnv (Env gbl lcl) (Maybe ModIface)
getIface
case Maybe ModIface
maybe_iface' of
Maybe ModIface
Nothing -> (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
MustCompile, Maybe ModIface
forall a. Maybe a
Nothing)
Just ModIface
iface -> HscEnv
-> ModSummary
-> ModIface
-> IfG (RecompileRequired, Maybe ModIface)
checkVersions HscEnv
hsc_env ModSummary
mod_summary ModIface
iface
checkVersions :: HscEnv
-> ModSummary
-> ModIface
-> IfG (RecompileRequired, Maybe ModIface)
checkVersions :: HscEnv
-> ModSummary
-> ModIface
-> IfG (RecompileRequired, Maybe ModIface)
checkVersions HscEnv
hsc_env ModSummary
mod_summary ModIface
iface
= do { SDoc -> IOEnv (Env IfGblEnv ()) ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (String -> SDoc
text String
"Considering whether compilation is required for" SDoc -> SDoc -> SDoc
<+>
Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface) SDoc -> SDoc -> SDoc
<> SDoc
colon)
; if Module -> UnitId
moduleUnitId (ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface) UnitId -> UnitId -> Bool
forall a. Eq a => a -> a -> Bool
/= DynFlags -> UnitId
thisPackage (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
then (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
"-this-unit-id changed", Maybe ModIface
forall a. Maybe a
Nothing) else do {
; RecompileRequired
recomp <- HscEnv -> ModIface -> IfG RecompileRequired
checkFlagHash HscEnv
hsc_env ModIface
iface
; if RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp then (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, Maybe ModIface
forall a. Maybe a
Nothing) else do {
; RecompileRequired
recomp <- HscEnv -> ModIface -> IfG RecompileRequired
checkOptimHash HscEnv
hsc_env ModIface
iface
; if RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp then (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, Maybe ModIface
forall a. Maybe a
Nothing) else do {
; RecompileRequired
recomp <- HscEnv -> ModIface -> IfG RecompileRequired
checkHpcHash HscEnv
hsc_env ModIface
iface
; if RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp then (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, Maybe ModIface
forall a. Maybe a
Nothing) else do {
; RecompileRequired
recomp <- ModSummary -> ModIface -> IfG RecompileRequired
checkMergedSignatures ModSummary
mod_summary ModIface
iface
; if RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp then (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, Maybe ModIface
forall a. Maybe a
Nothing) else do {
; RecompileRequired
recomp <- ModSummary -> ModIface -> IfG RecompileRequired
checkHsig ModSummary
mod_summary ModIface
iface
; if RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp then (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, Maybe ModIface
forall a. Maybe a
Nothing) else do {
; RecompileRequired
recomp <- ModSummary -> IfG RecompileRequired
checkHie ModSummary
mod_summary
; if RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp then (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, Maybe ModIface
forall a. Maybe a
Nothing) else do {
; RecompileRequired
recomp <- HscEnv -> ModSummary -> ModIface -> IfG RecompileRequired
checkDependencies HscEnv
hsc_env ModSummary
mod_summary ModIface
iface
; if RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp then (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, ModIface -> Maybe ModIface
forall a. a -> Maybe a
Just ModIface
iface) else do {
; RecompileRequired
recomp <- HscEnv -> ModIface -> IfG RecompileRequired
checkPlugins HscEnv
hsc_env ModIface
iface
; if RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp then (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, Maybe ModIface
forall a. Maybe a
Nothing) else do {
; (ExternalPackageState -> ExternalPackageState)
-> IOEnv (Env IfGblEnv ()) ()
forall gbl lcl.
(ExternalPackageState -> ExternalPackageState) -> TcRnIf gbl lcl ()
updateEps_ ((ExternalPackageState -> ExternalPackageState)
-> IOEnv (Env IfGblEnv ()) ())
-> (ExternalPackageState -> ExternalPackageState)
-> IOEnv (Env IfGblEnv ()) ()
forall a b. (a -> b) -> a -> b
$ \ExternalPackageState
eps -> ExternalPackageState
eps { eps_is_boot :: ModuleNameEnv (ModuleName, Bool)
eps_is_boot = ModuleNameEnv (ModuleName, Bool)
mod_deps }
; RecompileRequired
recomp <- [IfG RecompileRequired] -> IfG RecompileRequired
checkList [UnitId -> Usage -> IfG RecompileRequired
checkModUsage UnitId
this_pkg Usage
u | Usage
u <- ModIface -> [Usage]
forall (phase :: ModIfacePhase). ModIface_ phase -> [Usage]
mi_usages ModIface
iface]
; (RecompileRequired, Maybe ModIface)
-> IfG (RecompileRequired, Maybe ModIface)
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, ModIface -> Maybe ModIface
forall a. a -> Maybe a
Just ModIface
iface)
}}}}}}}}}}
where
this_pkg :: UnitId
this_pkg = DynFlags -> UnitId
thisPackage (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
mod_deps :: ModuleNameEnv (ModuleName, IsBootInterface)
mod_deps :: ModuleNameEnv (ModuleName, Bool)
mod_deps = [(ModuleName, Bool)] -> ModuleNameEnv (ModuleName, Bool)
mkModDeps (Dependencies -> [(ModuleName, Bool)]
dep_mods (ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface))
checkPlugins :: HscEnv -> ModIface -> IfG RecompileRequired
checkPlugins :: HscEnv -> ModIface -> IfG RecompileRequired
checkPlugins HscEnv
hsc ModIface
iface = IO RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RecompileRequired -> IfG RecompileRequired)
-> IO RecompileRequired -> IfG RecompileRequired
forall a b. (a -> b) -> a -> b
$ do
Fingerprint
new_fingerprint <- HscEnv -> IO Fingerprint
fingerprintPlugins HscEnv
hsc
let old_fingerprint :: Fingerprint
old_fingerprint = ModIfaceBackend -> Fingerprint
mi_plugin_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
PluginRecompile
pr <- [PluginRecompile] -> PluginRecompile
forall a. Monoid a => [a] -> a
mconcat ([PluginRecompile] -> PluginRecompile)
-> IO [PluginRecompile] -> IO PluginRecompile
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PluginWithArgs -> IO PluginRecompile)
-> [PluginWithArgs] -> IO [PluginRecompile]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM PluginWithArgs -> IO PluginRecompile
pluginRecompile' (DynFlags -> [PluginWithArgs]
plugins (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc))
RecompileRequired -> IO RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired -> IO RecompileRequired)
-> RecompileRequired -> IO RecompileRequired
forall a b. (a -> b) -> a -> b
$
Fingerprint -> Fingerprint -> PluginRecompile -> RecompileRequired
pluginRecompileToRecompileRequired Fingerprint
old_fingerprint Fingerprint
new_fingerprint PluginRecompile
pr
fingerprintPlugins :: HscEnv -> IO Fingerprint
fingerprintPlugins :: HscEnv -> IO Fingerprint
fingerprintPlugins HscEnv
hsc_env = do
[PluginWithArgs] -> IO Fingerprint
fingerprintPlugins' ([PluginWithArgs] -> IO Fingerprint)
-> [PluginWithArgs] -> IO Fingerprint
forall a b. (a -> b) -> a -> b
$ DynFlags -> [PluginWithArgs]
plugins (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
fingerprintPlugins' :: [PluginWithArgs] -> IO Fingerprint
fingerprintPlugins' :: [PluginWithArgs] -> IO Fingerprint
fingerprintPlugins' [PluginWithArgs]
plugins = do
PluginRecompile
res <- [PluginRecompile] -> PluginRecompile
forall a. Monoid a => [a] -> a
mconcat ([PluginRecompile] -> PluginRecompile)
-> IO [PluginRecompile] -> IO PluginRecompile
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PluginWithArgs -> IO PluginRecompile)
-> [PluginWithArgs] -> IO [PluginRecompile]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM PluginWithArgs -> IO PluginRecompile
pluginRecompile' [PluginWithArgs]
plugins
Fingerprint -> IO Fingerprint
forall (m :: * -> *) a. Monad m => a -> m a
return (Fingerprint -> IO Fingerprint) -> Fingerprint -> IO Fingerprint
forall a b. (a -> b) -> a -> b
$ case PluginRecompile
res of
PluginRecompile
NoForceRecompile -> String -> Fingerprint
fingerprintString String
"NoForceRecompile"
PluginRecompile
ForceRecompile -> String -> Fingerprint
fingerprintString String
"ForceRecompile"
(MaybeRecompile Fingerprint
fp) -> Fingerprint
fp
pluginRecompileToRecompileRequired
:: Fingerprint -> Fingerprint -> PluginRecompile -> RecompileRequired
pluginRecompileToRecompileRequired :: Fingerprint -> Fingerprint -> PluginRecompile -> RecompileRequired
pluginRecompileToRecompileRequired Fingerprint
old_fp Fingerprint
new_fp PluginRecompile
pr
| Fingerprint
old_fp Fingerprint -> Fingerprint -> Bool
forall a. Eq a => a -> a -> Bool
== Fingerprint
new_fp =
case PluginRecompile
pr of
PluginRecompile
NoForceRecompile -> RecompileRequired
UpToDate
MaybeRecompile Fingerprint
_ -> RecompileRequired
UpToDate
PluginRecompile
ForceRecompile -> String -> RecompileRequired
RecompBecause String
"Impure plugin forced recompilation"
| Fingerprint
old_fp Fingerprint -> [Fingerprint] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Fingerprint]
magic_fingerprints Bool -> Bool -> Bool
||
Fingerprint
new_fp Fingerprint -> [Fingerprint] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Fingerprint]
magic_fingerprints
= String -> RecompileRequired
RecompBecause String
"Plugins changed"
| Bool
otherwise =
let reason :: String
reason = String
"Plugin fingerprint changed" in
case PluginRecompile
pr of
PluginRecompile
ForceRecompile -> String -> RecompileRequired
RecompBecause String
reason
PluginRecompile
_ -> String -> RecompileRequired
RecompBecause String
reason
where
magic_fingerprints :: [Fingerprint]
magic_fingerprints =
[ String -> Fingerprint
fingerprintString String
"NoForceRecompile"
, String -> Fingerprint
fingerprintString String
"ForceRecompile"
]
checkHsig :: ModSummary -> ModIface -> IfG RecompileRequired
checkHsig :: ModSummary -> ModIface -> IfG RecompileRequired
checkHsig ModSummary
mod_summary ModIface
iface = do
DynFlags
dflags <- IOEnv (Env IfGblEnv ()) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
let outer_mod :: Module
outer_mod = ModSummary -> Module
ms_mod ModSummary
mod_summary
inner_mod :: Module
inner_mod = DynFlags -> ModuleName -> Module
canonicalizeHomeModule DynFlags
dflags (Module -> ModuleName
moduleName Module
outer_mod)
MASSERT( moduleUnitId outer_mod == thisPackage dflags )
case Module
inner_mod Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
== ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_semantic_module ModIface
iface of
Bool
True -> SDoc -> IfG RecompileRequired
up_to_date (String -> SDoc
text String
"implementing module unchanged")
Bool
False -> RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
"implementing module changed")
checkHie :: ModSummary -> IfG RecompileRequired
checkHie :: ModSummary -> IfG RecompileRequired
checkHie ModSummary
mod_summary = do
DynFlags
dflags <- IOEnv (Env IfGblEnv ()) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
let hie_date_opt :: Maybe UTCTime
hie_date_opt = ModSummary -> Maybe UTCTime
ms_hie_date ModSummary
mod_summary
hs_date :: UTCTime
hs_date = ModSummary -> UTCTime
ms_hs_date ModSummary
mod_summary
RecompileRequired -> IfG RecompileRequired
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RecompileRequired -> IfG RecompileRequired)
-> RecompileRequired -> IfG RecompileRequired
forall a b. (a -> b) -> a -> b
$ case GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_WriteHie DynFlags
dflags of
Bool
False -> RecompileRequired
UpToDate
Bool
True -> case Maybe UTCTime
hie_date_opt of
Maybe UTCTime
Nothing -> String -> RecompileRequired
RecompBecause String
"HIE file is missing"
Just UTCTime
hie_date
| UTCTime
hie_date UTCTime -> UTCTime -> Bool
forall a. Ord a => a -> a -> Bool
< UTCTime
hs_date
-> String -> RecompileRequired
RecompBecause String
"HIE file is out of date"
| Bool
otherwise
-> RecompileRequired
UpToDate
checkFlagHash :: HscEnv -> ModIface -> IfG RecompileRequired
checkFlagHash :: HscEnv -> ModIface -> IfG RecompileRequired
checkFlagHash HscEnv
hsc_env ModIface
iface = do
let old_hash :: Fingerprint
old_hash = ModIfaceBackend -> Fingerprint
mi_flag_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
Fingerprint
new_hash <- IO Fingerprint -> IOEnv (Env IfGblEnv ()) Fingerprint
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Fingerprint -> IOEnv (Env IfGblEnv ()) Fingerprint)
-> IO Fingerprint -> IOEnv (Env IfGblEnv ()) Fingerprint
forall a b. (a -> b) -> a -> b
$ DynFlags
-> Module -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintDynFlags (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
(ModIface -> Module
forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface)
BinHandle -> Name -> IO ()
putNameLiterally
case Fingerprint
old_hash Fingerprint -> Fingerprint -> Bool
forall a. Eq a => a -> a -> Bool
== Fingerprint
new_hash of
Bool
True -> SDoc -> IfG RecompileRequired
up_to_date (String -> SDoc
text String
"Module flags unchanged")
Bool
False -> String
-> SDoc -> Fingerprint -> Fingerprint -> IfG RecompileRequired
out_of_date_hash String
"flags changed"
(String -> SDoc
text String
" Module flags have changed")
Fingerprint
old_hash Fingerprint
new_hash
checkOptimHash :: HscEnv -> ModIface -> IfG RecompileRequired
checkOptimHash :: HscEnv -> ModIface -> IfG RecompileRequired
checkOptimHash HscEnv
hsc_env ModIface
iface = do
let old_hash :: Fingerprint
old_hash = ModIfaceBackend -> Fingerprint
mi_opt_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
Fingerprint
new_hash <- IO Fingerprint -> IOEnv (Env IfGblEnv ()) Fingerprint
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Fingerprint -> IOEnv (Env IfGblEnv ()) Fingerprint)
-> IO Fingerprint -> IOEnv (Env IfGblEnv ()) Fingerprint
forall a b. (a -> b) -> a -> b
$ DynFlags -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintOptFlags (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
BinHandle -> Name -> IO ()
putNameLiterally
if | Fingerprint
old_hash Fingerprint -> Fingerprint -> Bool
forall a. Eq a => a -> a -> Bool
== Fingerprint
new_hash
-> SDoc -> IfG RecompileRequired
up_to_date (String -> SDoc
text String
"Optimisation flags unchanged")
| GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_IgnoreOptimChanges (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
-> SDoc -> IfG RecompileRequired
up_to_date (String -> SDoc
text String
"Optimisation flags changed; ignoring")
| Bool
otherwise
-> String
-> SDoc -> Fingerprint -> Fingerprint -> IfG RecompileRequired
out_of_date_hash String
"Optimisation flags changed"
(String -> SDoc
text String
" Optimisation flags have changed")
Fingerprint
old_hash Fingerprint
new_hash
checkHpcHash :: HscEnv -> ModIface -> IfG RecompileRequired
checkHpcHash :: HscEnv -> ModIface -> IfG RecompileRequired
checkHpcHash HscEnv
hsc_env ModIface
iface = do
let old_hash :: Fingerprint
old_hash = ModIfaceBackend -> Fingerprint
mi_hpc_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
Fingerprint
new_hash <- IO Fingerprint -> IOEnv (Env IfGblEnv ()) Fingerprint
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Fingerprint -> IOEnv (Env IfGblEnv ()) Fingerprint)
-> IO Fingerprint -> IOEnv (Env IfGblEnv ()) Fingerprint
forall a b. (a -> b) -> a -> b
$ DynFlags -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintHpcFlags (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
BinHandle -> Name -> IO ()
putNameLiterally
if | Fingerprint
old_hash Fingerprint -> Fingerprint -> Bool
forall a. Eq a => a -> a -> Bool
== Fingerprint
new_hash
-> SDoc -> IfG RecompileRequired
up_to_date (String -> SDoc
text String
"HPC flags unchanged")
| GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_IgnoreHpcChanges (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
-> SDoc -> IfG RecompileRequired
up_to_date (String -> SDoc
text String
"HPC flags changed; ignoring")
| Bool
otherwise
-> String
-> SDoc -> Fingerprint -> Fingerprint -> IfG RecompileRequired
out_of_date_hash String
"HPC flags changed"
(String -> SDoc
text String
" HPC flags have changed")
Fingerprint
old_hash Fingerprint
new_hash
checkMergedSignatures :: ModSummary -> ModIface -> IfG RecompileRequired
checkMergedSignatures :: ModSummary -> ModIface -> IfG RecompileRequired
checkMergedSignatures ModSummary
mod_summary ModIface
iface = do
DynFlags
dflags <- IOEnv (Env IfGblEnv ()) DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
let old_merged :: [Module]
old_merged = [Module] -> [Module]
forall a. Ord a => [a] -> [a]
sort [ Module
mod | UsageMergedRequirement{ usg_mod :: Usage -> Module
usg_mod = Module
mod } <- ModIface -> [Usage]
forall (phase :: ModIfacePhase). ModIface_ phase -> [Usage]
mi_usages ModIface
iface ]
new_merged :: [Module]
new_merged = case ModuleName -> Map ModuleName [IndefModule] -> Maybe [IndefModule]
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (ModSummary -> ModuleName
ms_mod_name ModSummary
mod_summary)
(PackageState -> Map ModuleName [IndefModule]
requirementContext (DynFlags -> PackageState
pkgState DynFlags
dflags)) of
Maybe [IndefModule]
Nothing -> []
Just [IndefModule]
r -> [Module] -> [Module]
forall a. Ord a => [a] -> [a]
sort ([Module] -> [Module]) -> [Module] -> [Module]
forall a b. (a -> b) -> a -> b
$ (IndefModule -> Module) -> [IndefModule] -> [Module]
forall a b. (a -> b) -> [a] -> [b]
map (DynFlags -> IndefModule -> Module
indefModuleToModule DynFlags
dflags) [IndefModule]
r
if [Module]
old_merged [Module] -> [Module] -> Bool
forall a. Eq a => a -> a -> Bool
== [Module]
new_merged
then SDoc -> IfG RecompileRequired
up_to_date (String -> SDoc
text String
"signatures to merge in unchanged" SDoc -> SDoc -> SDoc
$$ [Module] -> SDoc
forall a. Outputable a => a -> SDoc
ppr [Module]
new_merged)
else RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
"signatures to merge in changed")
checkDependencies :: HscEnv -> ModSummary -> ModIface -> IfG RecompileRequired
checkDependencies :: HscEnv -> ModSummary -> ModIface -> IfG RecompileRequired
checkDependencies HscEnv
hsc_env ModSummary
summary ModIface
iface
= do
[IfG RecompileRequired] -> IfG RecompileRequired
checkList ([IfG RecompileRequired] -> IfG RecompileRequired)
-> [IfG RecompileRequired] -> IfG RecompileRequired
forall a b. (a -> b) -> a -> b
$
[ [IfG RecompileRequired] -> IfG RecompileRequired
checkList (((Maybe RuleName, GenLocated SrcSpan ModuleName)
-> IfG RecompileRequired)
-> [(Maybe RuleName, GenLocated SrcSpan ModuleName)]
-> [IfG RecompileRequired]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe RuleName, GenLocated SrcSpan ModuleName)
-> IfG RecompileRequired
forall l m n.
(Maybe RuleName, GenLocated l ModuleName)
-> IOEnv (Env m n) RecompileRequired
dep_missing (ModSummary -> [(Maybe RuleName, GenLocated SrcSpan ModuleName)]
ms_imps ModSummary
summary [(Maybe RuleName, GenLocated SrcSpan ModuleName)]
-> [(Maybe RuleName, GenLocated SrcSpan ModuleName)]
-> [(Maybe RuleName, GenLocated SrcSpan ModuleName)]
forall a. [a] -> [a] -> [a]
++ ModSummary -> [(Maybe RuleName, GenLocated SrcSpan ModuleName)]
ms_srcimps ModSummary
summary))
, do
(RecompileRequired
recomp, [[ModuleName]]
mnames_seen) <- [IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])]
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [[ModuleName]])
forall (m :: * -> *) a.
Monad m =>
[m (RecompileRequired, a)] -> m (RecompileRequired, [a])
runUntilRecompRequired ([IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])]
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [[ModuleName]]))
-> [IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])]
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [[ModuleName]])
forall a b. (a -> b) -> a -> b
$ (GenLocated SrcSpan ModuleName
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName]))
-> [GenLocated SrcSpan ModuleName]
-> [IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])]
forall a b. (a -> b) -> [a] -> [b]
map
GenLocated SrcSpan ModuleName
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])
forall l.
GenLocated l ModuleName
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])
checkForNewHomeDependency
(ModSummary -> [GenLocated SrcSpan ModuleName]
ms_home_imps ModSummary
summary)
case RecompileRequired
recomp of
RecompileRequired
UpToDate -> do
let
seen_home_deps :: Set ModuleName
seen_home_deps = [Set ModuleName] -> Set ModuleName
forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a
Set.unions ([Set ModuleName] -> Set ModuleName)
-> [Set ModuleName] -> Set ModuleName
forall a b. (a -> b) -> a -> b
$ ([ModuleName] -> Set ModuleName)
-> [[ModuleName]] -> [Set ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map [ModuleName] -> Set ModuleName
forall a. Ord a => [a] -> Set a
Set.fromList [[ModuleName]]
mnames_seen
Set ModuleName -> IfG RecompileRequired
forall m n. Set ModuleName -> IOEnv (Env m n) RecompileRequired
checkIfAllOldHomeDependenciesAreSeen Set ModuleName
seen_home_deps
RecompileRequired
_ -> RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recomp]
where
prev_dep_mods :: [(ModuleName, Bool)]
prev_dep_mods = Dependencies -> [(ModuleName, Bool)]
dep_mods (ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface)
prev_dep_plgn :: [ModuleName]
prev_dep_plgn = Dependencies -> [ModuleName]
dep_plgins (ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface)
prev_dep_pkgs :: [(InstalledUnitId, Bool)]
prev_dep_pkgs = Dependencies -> [(InstalledUnitId, Bool)]
dep_pkgs (ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface)
this_pkg :: UnitId
this_pkg = DynFlags -> UnitId
thisPackage (HscEnv -> DynFlags
hsc_dflags HscEnv
hsc_env)
dep_missing :: (Maybe RuleName, GenLocated l ModuleName)
-> IOEnv (Env m n) RecompileRequired
dep_missing (Maybe RuleName
mb_pkg, L l
_ ModuleName
mod) = do
FindResult
find_res <- IO FindResult -> IOEnv (Env m n) FindResult
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FindResult -> IOEnv (Env m n) FindResult)
-> IO FindResult -> IOEnv (Env m n) FindResult
forall a b. (a -> b) -> a -> b
$ HscEnv -> ModuleName -> Maybe RuleName -> IO FindResult
findImportedModule HscEnv
hsc_env ModuleName
mod (Maybe RuleName
mb_pkg)
let reason :: String
reason = ModuleName -> String
moduleNameString ModuleName
mod String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" changed"
case FindResult
find_res of
Found ModLocation
_ Module
mod
| UnitId
pkg UnitId -> UnitId -> Bool
forall a. Eq a => a -> a -> Bool
== UnitId
this_pkg
-> if Module -> ModuleName
moduleName Module
mod ModuleName -> [ModuleName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` ((ModuleName, Bool) -> ModuleName)
-> [(ModuleName, Bool)] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map (ModuleName, Bool) -> ModuleName
forall a b. (a, b) -> a
fst [(ModuleName, Bool)]
prev_dep_mods [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ [ModuleName]
prev_dep_plgn
then do SDoc -> TcRnIf m n ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (SDoc -> TcRnIf m n ()) -> SDoc -> TcRnIf m n ()
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"imported module " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" not among previous dependencies"
RecompileRequired -> IOEnv (Env m n) RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
reason)
else
RecompileRequired -> IOEnv (Env m n) RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
| Bool
otherwise
-> if UnitId -> InstalledUnitId
toInstalledUnitId UnitId
pkg InstalledUnitId -> [InstalledUnitId] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` (((InstalledUnitId, Bool) -> InstalledUnitId)
-> [(InstalledUnitId, Bool)] -> [InstalledUnitId]
forall a b. (a -> b) -> [a] -> [b]
map (InstalledUnitId, Bool) -> InstalledUnitId
forall a b. (a, b) -> a
fst [(InstalledUnitId, Bool)]
prev_dep_pkgs)
then do SDoc -> TcRnIf m n ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (SDoc -> TcRnIf m n ()) -> SDoc -> TcRnIf m n ()
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"imported module " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" is from package " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (UnitId -> SDoc
forall a. Outputable a => a -> SDoc
ppr UnitId
pkg) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
", which is not among previous dependencies"
RecompileRequired -> IOEnv (Env m n) RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
reason)
else
RecompileRequired -> IOEnv (Env m n) RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
where pkg :: UnitId
pkg = Module -> UnitId
moduleUnitId Module
mod
FindResult
_otherwise -> RecompileRequired -> IOEnv (Env m n) RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
reason)
old_deps :: Set ModuleName
old_deps = [ModuleName] -> Set ModuleName
forall a. Ord a => [a] -> Set a
Set.fromList ([ModuleName] -> Set ModuleName) -> [ModuleName] -> Set ModuleName
forall a b. (a -> b) -> a -> b
$ ((ModuleName, Bool) -> ModuleName)
-> [(ModuleName, Bool)] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map (ModuleName, Bool) -> ModuleName
forall a b. (a, b) -> a
fst ([(ModuleName, Bool)] -> [ModuleName])
-> [(ModuleName, Bool)] -> [ModuleName]
forall a b. (a -> b) -> a -> b
$ ((ModuleName, Bool) -> Bool)
-> [(ModuleName, Bool)] -> [(ModuleName, Bool)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((ModuleName, Bool) -> Bool) -> (ModuleName, Bool) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ModuleName, Bool) -> Bool
forall a b. (a, b) -> b
snd) [(ModuleName, Bool)]
prev_dep_mods
isOldHomeDeps :: ModuleName -> Bool
isOldHomeDeps = (ModuleName -> Set ModuleName -> Bool)
-> Set ModuleName -> ModuleName -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip ModuleName -> Set ModuleName -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member Set ModuleName
old_deps
checkForNewHomeDependency :: GenLocated l ModuleName
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])
checkForNewHomeDependency (L l
_ ModuleName
mname) = do
let
mod :: Module
mod = UnitId -> ModuleName -> Module
mkModule UnitId
this_pkg ModuleName
mname
str_mname :: String
str_mname = ModuleName -> String
moduleNameString ModuleName
mname
reason :: String
reason = String
str_mname String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" changed"
if Bool -> Bool
not (ModuleName -> Bool
isOldHomeDeps ModuleName
mname)
then (RecompileRequired, [ModuleName])
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
UpToDate, [])
else do
Maybe (RecompileRequired, [ModuleName])
mb_result <- String
-> Module
-> (ModIface
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName]))
-> IfG (Maybe (RecompileRequired, [ModuleName]))
forall a. String -> Module -> (ModIface -> IfG a) -> IfG (Maybe a)
getFromModIface String
"need mi_deps for" Module
mod ((ModIface
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName]))
-> IfG (Maybe (RecompileRequired, [ModuleName])))
-> (ModIface
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName]))
-> IfG (Maybe (RecompileRequired, [ModuleName]))
forall a b. (a -> b) -> a -> b
$ \ModIface
imported_iface -> do
let mnames :: [ModuleName]
mnames = ModuleName
mnameModuleName -> [ModuleName] -> [ModuleName]
forall a. a -> [a] -> [a]
:(((ModuleName, Bool) -> ModuleName)
-> [(ModuleName, Bool)] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map (ModuleName, Bool) -> ModuleName
forall a b. (a, b) -> a
fst ([(ModuleName, Bool)] -> [ModuleName])
-> [(ModuleName, Bool)] -> [ModuleName]
forall a b. (a -> b) -> a -> b
$ ((ModuleName, Bool) -> Bool)
-> [(ModuleName, Bool)] -> [(ModuleName, Bool)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((ModuleName, Bool) -> Bool) -> (ModuleName, Bool) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ModuleName, Bool) -> Bool
forall a b. (a, b) -> b
snd) ([(ModuleName, Bool)] -> [(ModuleName, Bool)])
-> [(ModuleName, Bool)] -> [(ModuleName, Bool)]
forall a b. (a -> b) -> a -> b
$
Dependencies -> [(ModuleName, Bool)]
dep_mods (Dependencies -> [(ModuleName, Bool)])
-> Dependencies -> [(ModuleName, Bool)]
forall a b. (a -> b) -> a -> b
$ ModIface -> Dependencies
forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
imported_iface)
case (ModuleName -> Bool) -> [ModuleName] -> Maybe ModuleName
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Bool -> Bool
not (Bool -> Bool) -> (ModuleName -> Bool) -> ModuleName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleName -> Bool
isOldHomeDeps) [ModuleName]
mnames of
Maybe ModuleName
Nothing -> (RecompileRequired, [ModuleName])
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
UpToDate, [ModuleName]
mnames)
Just ModuleName
new_dep_mname -> do
SDoc -> IOEnv (Env IfGblEnv ()) ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (SDoc -> IOEnv (Env IfGblEnv ()) ())
-> SDoc -> IOEnv (Env IfGblEnv ()) ()
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"imported home module " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" has a new dependency " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
new_dep_mname)
(RecompileRequired, [ModuleName])
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
reason, [])
(RecompileRequired, [ModuleName])
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])
forall (m :: * -> *) a. Monad m => a -> m a
return ((RecompileRequired, [ModuleName])
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName]))
-> (RecompileRequired, [ModuleName])
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])
forall a b. (a -> b) -> a -> b
$ (RecompileRequired, [ModuleName])
-> Maybe (RecompileRequired, [ModuleName])
-> (RecompileRequired, [ModuleName])
forall a. a -> Maybe a -> a
fromMaybe (RecompileRequired
MustCompile, []) Maybe (RecompileRequired, [ModuleName])
mb_result
runUntilRecompRequired :: [m (RecompileRequired, a)] -> m (RecompileRequired, [a])
runUntilRecompRequired [] = (RecompileRequired, [a]) -> m (RecompileRequired, [a])
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
UpToDate, [])
runUntilRecompRequired (m (RecompileRequired, a)
check:[m (RecompileRequired, a)]
checks) = do
(RecompileRequired
recompile, a
value) <- m (RecompileRequired, a)
check
if RecompileRequired -> Bool
recompileRequired RecompileRequired
recompile
then (RecompileRequired, [a]) -> m (RecompileRequired, [a])
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recompile, [])
else do
(RecompileRequired
recomp, [a]
values) <- [m (RecompileRequired, a)] -> m (RecompileRequired, [a])
runUntilRecompRequired [m (RecompileRequired, a)]
checks
(RecompileRequired, [a]) -> m (RecompileRequired, [a])
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, a
valuea -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
values)
checkIfAllOldHomeDependenciesAreSeen :: Set ModuleName -> IOEnv (Env m n) RecompileRequired
checkIfAllOldHomeDependenciesAreSeen Set ModuleName
seen_deps = do
let unseen_old_deps :: Set ModuleName
unseen_old_deps = Set ModuleName -> Set ModuleName -> Set ModuleName
forall a. Ord a => Set a -> Set a -> Set a
Set.difference
Set ModuleName
old_deps
Set ModuleName
seen_deps
if Bool -> Bool
not (Set ModuleName -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Set ModuleName
unseen_old_deps)
then do
let missing_dep :: ModuleName
missing_dep = Int -> Set ModuleName -> ModuleName
forall a. Int -> Set a -> a
Set.elemAt Int
0 Set ModuleName
unseen_old_deps
SDoc -> TcRnIf m n ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (SDoc -> TcRnIf m n ()) -> SDoc -> TcRnIf m n ()
forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"missing old home dependency " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (ModuleName -> SDoc
forall a. Outputable a => a -> SDoc
ppr ModuleName
missing_dep)
RecompileRequired -> IOEnv (Env m n) RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired -> IOEnv (Env m n) RecompileRequired)
-> RecompileRequired -> IOEnv (Env m n) RecompileRequired
forall a b. (a -> b) -> a -> b
$ String -> RecompileRequired
RecompBecause String
"missing old dependency"
else RecompileRequired -> IOEnv (Env m n) RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
needInterface :: Module -> (ModIface -> IfG RecompileRequired)
-> IfG RecompileRequired
needInterface :: Module
-> (ModIface -> IfG RecompileRequired) -> IfG RecompileRequired
needInterface Module
mod ModIface -> IfG RecompileRequired
continue
= do
Maybe RecompileRequired
mb_recomp <- String
-> Module
-> (ModIface -> IfG RecompileRequired)
-> IfG (Maybe RecompileRequired)
forall a. String -> Module -> (ModIface -> IfG a) -> IfG (Maybe a)
getFromModIface
String
"need version info for"
Module
mod
ModIface -> IfG RecompileRequired
continue
case Maybe RecompileRequired
mb_recomp of
Maybe RecompileRequired
Nothing -> RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
MustCompile
Just RecompileRequired
recomp -> RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recomp
getFromModIface :: String -> Module -> (ModIface -> IfG a)
-> IfG (Maybe a)
getFromModIface :: String -> Module -> (ModIface -> IfG a) -> IfG (Maybe a)
getFromModIface String
doc_msg Module
mod ModIface -> IfG a
getter
= do
let doc_str :: SDoc
doc_str = [SDoc] -> SDoc
sep [String -> SDoc
text String
doc_msg, Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod]
SDoc -> IOEnv (Env IfGblEnv ()) ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (String -> SDoc
text String
"Checking innterface for module" SDoc -> SDoc -> SDoc
<+> Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod)
MaybeErr SDoc ModIface
mb_iface <- SDoc
-> Module
-> WhereFrom
-> TcRnIf IfGblEnv () (MaybeErr SDoc ModIface)
forall lcl.
SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr SDoc ModIface)
loadInterface SDoc
doc_str Module
mod WhereFrom
ImportBySystem
case MaybeErr SDoc ModIface
mb_iface of
Failed SDoc
_ -> do
SDoc -> IOEnv (Env IfGblEnv ()) ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs ([SDoc] -> SDoc
sep [String -> SDoc
text String
"Couldn't load interface for module",
Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod])
Maybe a -> IfG (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
Succeeded ModIface
iface -> a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> IfG a -> IfG (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ModIface -> IfG a
getter ModIface
iface
checkModUsage :: UnitId -> Usage -> IfG RecompileRequired
checkModUsage :: UnitId -> Usage -> IfG RecompileRequired
checkModUsage UnitId
_this_pkg UsagePackageModule{
usg_mod :: Usage -> Module
usg_mod = Module
mod,
usg_mod_hash :: Usage -> Fingerprint
usg_mod_hash = Fingerprint
old_mod_hash }
= Module
-> (ModIface -> IfG RecompileRequired) -> IfG RecompileRequired
needInterface Module
mod ((ModIface -> IfG RecompileRequired) -> IfG RecompileRequired)
-> (ModIface -> IfG RecompileRequired) -> IfG RecompileRequired
forall a b. (a -> b) -> a -> b
$ \ModIface
iface -> do
let reason :: String
reason = ModuleName -> String
moduleNameString (Module -> ModuleName
moduleName Module
mod) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" changed"
String -> Fingerprint -> Fingerprint -> IfG RecompileRequired
checkModuleFingerprint String
reason Fingerprint
old_mod_hash (ModIfaceBackend -> Fingerprint
mi_mod_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface))
checkModUsage UnitId
_ UsageMergedRequirement{ usg_mod :: Usage -> Module
usg_mod = Module
mod, usg_mod_hash :: Usage -> Fingerprint
usg_mod_hash = Fingerprint
old_mod_hash }
= Module
-> (ModIface -> IfG RecompileRequired) -> IfG RecompileRequired
needInterface Module
mod ((ModIface -> IfG RecompileRequired) -> IfG RecompileRequired)
-> (ModIface -> IfG RecompileRequired) -> IfG RecompileRequired
forall a b. (a -> b) -> a -> b
$ \ModIface
iface -> do
let reason :: String
reason = ModuleName -> String
moduleNameString (Module -> ModuleName
moduleName Module
mod) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" changed (raw)"
String -> Fingerprint -> Fingerprint -> IfG RecompileRequired
checkModuleFingerprint String
reason Fingerprint
old_mod_hash (ModIfaceBackend -> Fingerprint
mi_mod_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface))
checkModUsage UnitId
this_pkg UsageHomeModule{
usg_mod_name :: Usage -> ModuleName
usg_mod_name = ModuleName
mod_name,
usg_mod_hash :: Usage -> Fingerprint
usg_mod_hash = Fingerprint
old_mod_hash,
usg_exports :: Usage -> Maybe Fingerprint
usg_exports = Maybe Fingerprint
maybe_old_export_hash,
usg_entities :: Usage -> [(OccName, Fingerprint)]
usg_entities = [(OccName, Fingerprint)]
old_decl_hash }
= do
let mod :: Module
mod = UnitId -> ModuleName -> Module
mkModule UnitId
this_pkg ModuleName
mod_name
Module
-> (ModIface -> IfG RecompileRequired) -> IfG RecompileRequired
needInterface Module
mod ((ModIface -> IfG RecompileRequired) -> IfG RecompileRequired)
-> (ModIface -> IfG RecompileRequired) -> IfG RecompileRequired
forall a b. (a -> b) -> a -> b
$ \ModIface
iface -> do
let
new_mod_hash :: Fingerprint
new_mod_hash = ModIfaceBackend -> Fingerprint
mi_mod_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
new_decl_hash :: OccName -> Maybe (OccName, Fingerprint)
new_decl_hash = ModIfaceBackend -> OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
new_export_hash :: Fingerprint
new_export_hash = ModIfaceBackend -> Fingerprint
mi_exp_hash (ModIface -> IfaceBackendExts 'ModIfaceFinal
forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
reason :: String
reason = ModuleName -> String
moduleNameString ModuleName
mod_name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" changed"
RecompileRequired
recompile <- String -> Fingerprint -> Fingerprint -> IfG RecompileRequired
checkModuleFingerprint String
reason Fingerprint
old_mod_hash Fingerprint
new_mod_hash
if Bool -> Bool
not (RecompileRequired -> Bool
recompileRequired RecompileRequired
recompile)
then RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
else do
String
-> Maybe Fingerprint
-> Fingerprint
-> SDoc
-> IfG RecompileRequired
-> IfG RecompileRequired
checkMaybeHash String
reason Maybe Fingerprint
maybe_old_export_hash Fingerprint
new_export_hash
(String -> SDoc
text String
" Export list changed") (IfG RecompileRequired -> IfG RecompileRequired)
-> IfG RecompileRequired -> IfG RecompileRequired
forall a b. (a -> b) -> a -> b
$ do
RecompileRequired
recompile <- [IfG RecompileRequired] -> IfG RecompileRequired
checkList [ String
-> (OccName -> Maybe (OccName, Fingerprint))
-> (OccName, Fingerprint)
-> IfG RecompileRequired
checkEntityUsage String
reason OccName -> Maybe (OccName, Fingerprint)
new_decl_hash (OccName, Fingerprint)
u
| (OccName, Fingerprint)
u <- [(OccName, Fingerprint)]
old_decl_hash]
if RecompileRequired -> Bool
recompileRequired RecompileRequired
recompile
then RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recompile
else SDoc -> IfG RecompileRequired
up_to_date (String -> SDoc
text String
" Great! The bits I use are up to date")
checkModUsage UnitId
_this_pkg UsageFile{ usg_file_path :: Usage -> String
usg_file_path = String
file,
usg_file_hash :: Usage -> Fingerprint
usg_file_hash = Fingerprint
old_hash } =
IO RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RecompileRequired -> IfG RecompileRequired)
-> IO RecompileRequired -> IfG RecompileRequired
forall a b. (a -> b) -> a -> b
$
(IOException -> IO RecompileRequired)
-> IO RecompileRequired -> IO RecompileRequired
forall a. (IOException -> IO a) -> IO a -> IO a
handleIO IOException -> IO RecompileRequired
forall p. p -> IO RecompileRequired
handle (IO RecompileRequired -> IO RecompileRequired)
-> IO RecompileRequired -> IO RecompileRequired
forall a b. (a -> b) -> a -> b
$ do
Fingerprint
new_hash <- String -> IO Fingerprint
getFileHash String
file
if (Fingerprint
old_hash Fingerprint -> Fingerprint -> Bool
forall a. Eq a => a -> a -> Bool
/= Fingerprint
new_hash)
then RecompileRequired -> IO RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recomp
else RecompileRequired -> IO RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
where
recomp :: RecompileRequired
recomp = String -> RecompileRequired
RecompBecause (String
file String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" changed")
handle :: p -> IO RecompileRequired
handle =
#if defined(DEBUG)
\e -> pprTrace "UsageFile" (text (show e)) $ return recomp
#else
\p
_ -> RecompileRequired -> IO RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recomp
#endif
checkModuleFingerprint :: String -> Fingerprint -> Fingerprint
-> IfG RecompileRequired
checkModuleFingerprint :: String -> Fingerprint -> Fingerprint -> IfG RecompileRequired
checkModuleFingerprint String
reason Fingerprint
old_mod_hash Fingerprint
new_mod_hash
| Fingerprint
new_mod_hash Fingerprint -> Fingerprint -> Bool
forall a. Eq a => a -> a -> Bool
== Fingerprint
old_mod_hash
= SDoc -> IfG RecompileRequired
up_to_date (String -> SDoc
text String
"Module fingerprint unchanged")
| Bool
otherwise
= String
-> SDoc -> Fingerprint -> Fingerprint -> IfG RecompileRequired
out_of_date_hash String
reason (String -> SDoc
text String
" Module fingerprint has changed")
Fingerprint
old_mod_hash Fingerprint
new_mod_hash
checkMaybeHash :: String -> Maybe Fingerprint -> Fingerprint -> SDoc
-> IfG RecompileRequired -> IfG RecompileRequired
checkMaybeHash :: String
-> Maybe Fingerprint
-> Fingerprint
-> SDoc
-> IfG RecompileRequired
-> IfG RecompileRequired
checkMaybeHash String
reason Maybe Fingerprint
maybe_old_hash Fingerprint
new_hash SDoc
doc IfG RecompileRequired
continue
| Just Fingerprint
hash <- Maybe Fingerprint
maybe_old_hash, Fingerprint
hash Fingerprint -> Fingerprint -> Bool
forall a. Eq a => a -> a -> Bool
/= Fingerprint
new_hash
= String
-> SDoc -> Fingerprint -> Fingerprint -> IfG RecompileRequired
out_of_date_hash String
reason SDoc
doc Fingerprint
hash Fingerprint
new_hash
| Bool
otherwise
= IfG RecompileRequired
continue
checkEntityUsage :: String
-> (OccName -> Maybe (OccName, Fingerprint))
-> (OccName, Fingerprint)
-> IfG RecompileRequired
checkEntityUsage :: String
-> (OccName -> Maybe (OccName, Fingerprint))
-> (OccName, Fingerprint)
-> IfG RecompileRequired
checkEntityUsage String
reason OccName -> Maybe (OccName, Fingerprint)
new_hash (OccName
name,Fingerprint
old_hash)
= case OccName -> Maybe (OccName, Fingerprint)
new_hash OccName
name of
Maybe (OccName, Fingerprint)
Nothing ->
String -> SDoc -> IfG RecompileRequired
out_of_date String
reason ([SDoc] -> SDoc
sep [String -> SDoc
text String
"No longer exported:", OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
name])
Just (OccName
_, Fingerprint
new_hash)
| Fingerprint
new_hash Fingerprint -> Fingerprint -> Bool
forall a. Eq a => a -> a -> Bool
== Fingerprint
old_hash -> do SDoc -> IOEnv (Env IfGblEnv ()) ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (String -> SDoc
text String
" Up to date" SDoc -> SDoc -> SDoc
<+> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
name SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
new_hash))
RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
| Bool
otherwise -> String
-> SDoc -> Fingerprint -> Fingerprint -> IfG RecompileRequired
out_of_date_hash String
reason (String -> SDoc
text String
" Out of date:" SDoc -> SDoc -> SDoc
<+> OccName -> SDoc
forall a. Outputable a => a -> SDoc
ppr OccName
name)
Fingerprint
old_hash Fingerprint
new_hash
up_to_date :: SDoc -> IfG RecompileRequired
up_to_date :: SDoc -> IfG RecompileRequired
up_to_date SDoc
msg = SDoc -> IOEnv (Env IfGblEnv ()) ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs SDoc
msg IOEnv (Env IfGblEnv ()) ()
-> IfG RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
out_of_date :: String -> SDoc -> IfG RecompileRequired
out_of_date :: String -> SDoc -> IfG RecompileRequired
out_of_date String
reason SDoc
msg = SDoc -> IOEnv (Env IfGblEnv ()) ()
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs SDoc
msg IOEnv (Env IfGblEnv ()) ()
-> IfG RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
reason)
out_of_date_hash :: String -> SDoc -> Fingerprint -> Fingerprint -> IfG RecompileRequired
out_of_date_hash :: String
-> SDoc -> Fingerprint -> Fingerprint -> IfG RecompileRequired
out_of_date_hash String
reason SDoc
msg Fingerprint
old_hash Fingerprint
new_hash
= String -> SDoc -> IfG RecompileRequired
out_of_date String
reason ([SDoc] -> SDoc
hsep [SDoc
msg, Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
old_hash, String -> SDoc
text String
"->", Fingerprint -> SDoc
forall a. Outputable a => a -> SDoc
ppr Fingerprint
new_hash])
checkList :: [IfG RecompileRequired] -> IfG RecompileRequired
checkList :: [IfG RecompileRequired] -> IfG RecompileRequired
checkList [] = RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
checkList (IfG RecompileRequired
check:[IfG RecompileRequired]
checks) = do RecompileRequired
recompile <- IfG RecompileRequired
check
if RecompileRequired -> Bool
recompileRequired RecompileRequired
recompile
then RecompileRequired -> IfG RecompileRequired
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recompile
else [IfG RecompileRequired] -> IfG RecompileRequired
checkList [IfG RecompileRequired]
checks
tyThingToIfaceDecl :: TyThing -> IfaceDecl
tyThingToIfaceDecl :: TyThing -> IfaceDecl
tyThingToIfaceDecl (AnId Id
id) = Id -> IfaceDecl
idToIfaceDecl Id
id
tyThingToIfaceDecl (ATyCon TyCon
tycon) = (TidyEnv, IfaceDecl) -> IfaceDecl
forall a b. (a, b) -> b
snd (TidyEnv -> TyCon -> (TidyEnv, IfaceDecl)
tyConToIfaceDecl TidyEnv
emptyTidyEnv TyCon
tycon)
tyThingToIfaceDecl (ACoAxiom CoAxiom Branched
ax) = CoAxiom Branched -> IfaceDecl
forall (br :: BranchFlag). CoAxiom br -> IfaceDecl
coAxiomToIfaceDecl CoAxiom Branched
ax
tyThingToIfaceDecl (AConLike ConLike
cl) = case ConLike
cl of
RealDataCon DataCon
dc -> DataCon -> IfaceDecl
dataConToIfaceDecl DataCon
dc
PatSynCon PatSyn
ps -> PatSyn -> IfaceDecl
patSynToIfaceDecl PatSyn
ps
idToIfaceDecl :: Id -> IfaceDecl
idToIfaceDecl :: Id -> IfaceDecl
idToIfaceDecl Id
id
= IfaceId :: Name -> IfaceType -> IfaceIdDetails -> IfaceIdInfo -> IfaceDecl
IfaceId { ifName :: Name
ifName = Id -> Name
forall a. NamedThing a => a -> Name
getName Id
id,
ifType :: IfaceType
ifType = Type -> IfaceType
toIfaceType (Id -> Type
idType Id
id),
ifIdDetails :: IfaceIdDetails
ifIdDetails = IdDetails -> IfaceIdDetails
toIfaceIdDetails (Id -> IdDetails
idDetails Id
id),
ifIdInfo :: IfaceIdInfo
ifIdInfo = IdInfo -> IfaceIdInfo
toIfaceIdInfo (HasDebugCallStack => Id -> IdInfo
Id -> IdInfo
idInfo Id
id) }
dataConToIfaceDecl :: DataCon -> IfaceDecl
dataConToIfaceDecl :: DataCon -> IfaceDecl
dataConToIfaceDecl DataCon
dataCon
= IfaceId :: Name -> IfaceType -> IfaceIdDetails -> IfaceIdInfo -> IfaceDecl
IfaceId { ifName :: Name
ifName = DataCon -> Name
forall a. NamedThing a => a -> Name
getName DataCon
dataCon,
ifType :: IfaceType
ifType = Type -> IfaceType
toIfaceType (DataCon -> Type
dataConUserType DataCon
dataCon),
ifIdDetails :: IfaceIdDetails
ifIdDetails = IfaceIdDetails
IfVanillaId,
ifIdInfo :: IfaceIdInfo
ifIdInfo = IfaceIdInfo
NoInfo }
coAxiomToIfaceDecl :: CoAxiom br -> IfaceDecl
coAxiomToIfaceDecl :: CoAxiom br -> IfaceDecl
coAxiomToIfaceDecl ax :: CoAxiom br
ax@(CoAxiom { co_ax_tc :: forall (br :: BranchFlag). CoAxiom br -> TyCon
co_ax_tc = TyCon
tycon, co_ax_branches :: forall (br :: BranchFlag). CoAxiom br -> Branches br
co_ax_branches = Branches br
branches
, co_ax_role :: forall (br :: BranchFlag). CoAxiom br -> Role
co_ax_role = Role
role })
= IfaceAxiom :: Name -> IfaceTyCon -> Role -> [IfaceAxBranch] -> IfaceDecl
IfaceAxiom { ifName :: Name
ifName = CoAxiom br -> Name
forall a. NamedThing a => a -> Name
getName CoAxiom br
ax
, ifTyCon :: IfaceTyCon
ifTyCon = TyCon -> IfaceTyCon
toIfaceTyCon TyCon
tycon
, ifRole :: Role
ifRole = Role
role
, ifAxBranches :: [IfaceAxBranch]
ifAxBranches = (CoAxBranch -> IfaceAxBranch) -> [CoAxBranch] -> [IfaceAxBranch]
forall a b. (a -> b) -> [a] -> [b]
map (TyCon -> [[Type]] -> CoAxBranch -> IfaceAxBranch
coAxBranchToIfaceBranch TyCon
tycon
((CoAxBranch -> [Type]) -> [CoAxBranch] -> [[Type]]
forall a b. (a -> b) -> [a] -> [b]
map CoAxBranch -> [Type]
coAxBranchLHS [CoAxBranch]
branch_list))
[CoAxBranch]
branch_list }
where
branch_list :: [CoAxBranch]
branch_list = Branches br -> [CoAxBranch]
forall (br :: BranchFlag). Branches br -> [CoAxBranch]
fromBranches Branches br
branches
coAxBranchToIfaceBranch :: TyCon -> [[Type]] -> CoAxBranch -> IfaceAxBranch
coAxBranchToIfaceBranch :: TyCon -> [[Type]] -> CoAxBranch -> IfaceAxBranch
coAxBranchToIfaceBranch TyCon
tc [[Type]]
lhs_s
(CoAxBranch { cab_tvs :: CoAxBranch -> [Id]
cab_tvs = [Id]
tvs, cab_cvs :: CoAxBranch -> [Id]
cab_cvs = [Id]
cvs
, cab_eta_tvs :: CoAxBranch -> [Id]
cab_eta_tvs = [Id]
eta_tvs
, cab_lhs :: CoAxBranch -> [Type]
cab_lhs = [Type]
lhs, cab_roles :: CoAxBranch -> [Role]
cab_roles = [Role]
roles
, cab_rhs :: CoAxBranch -> Type
cab_rhs = Type
rhs, cab_incomps :: CoAxBranch -> [CoAxBranch]
cab_incomps = [CoAxBranch]
incomps })
= IfaceAxBranch :: [IfaceTvBndr]
-> [IfaceTvBndr]
-> [IfaceTvBndr]
-> IfaceAppArgs
-> [Role]
-> IfaceType
-> [Int]
-> IfaceAxBranch
IfaceAxBranch { ifaxbTyVars :: [IfaceTvBndr]
ifaxbTyVars = [Id] -> [IfaceTvBndr]
toIfaceTvBndrs [Id]
tvs
, ifaxbCoVars :: [IfaceTvBndr]
ifaxbCoVars = (Id -> IfaceTvBndr) -> [Id] -> [IfaceTvBndr]
forall a b. (a -> b) -> [a] -> [b]
map Id -> IfaceTvBndr
toIfaceIdBndr [Id]
cvs
, ifaxbEtaTyVars :: [IfaceTvBndr]
ifaxbEtaTyVars = [Id] -> [IfaceTvBndr]
toIfaceTvBndrs [Id]
eta_tvs
, ifaxbLHS :: IfaceAppArgs
ifaxbLHS = TyCon -> [Type] -> IfaceAppArgs
toIfaceTcArgs TyCon
tc [Type]
lhs
, ifaxbRoles :: [Role]
ifaxbRoles = [Role]
roles
, ifaxbRHS :: IfaceType
ifaxbRHS = Type -> IfaceType
toIfaceType Type
rhs
, ifaxbIncomps :: [Int]
ifaxbIncomps = [Int]
iface_incomps }
where
iface_incomps :: [Int]
iface_incomps = (CoAxBranch -> Int) -> [CoAxBranch] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Maybe Int -> Int
forall a. HasCallStack => String -> Maybe a -> a
expectJust String
"iface_incomps"
(Maybe Int -> Int)
-> (CoAxBranch -> Maybe Int) -> CoAxBranch -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([Type] -> Bool) -> [[Type]] -> Maybe Int)
-> [[Type]] -> ([Type] -> Bool) -> Maybe Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip ([Type] -> Bool) -> [[Type]] -> Maybe Int
forall a. (a -> Bool) -> [a] -> Maybe Int
findIndex [[Type]]
lhs_s
(([Type] -> Bool) -> Maybe Int)
-> (CoAxBranch -> [Type] -> Bool) -> CoAxBranch -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Type] -> [Type] -> Bool
eqTypes
([Type] -> [Type] -> Bool)
-> (CoAxBranch -> [Type]) -> CoAxBranch -> [Type] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CoAxBranch -> [Type]
coAxBranchLHS) [CoAxBranch]
incomps
tyConToIfaceDecl :: TidyEnv -> TyCon -> (TidyEnv, IfaceDecl)
tyConToIfaceDecl :: TidyEnv -> TyCon -> (TidyEnv, IfaceDecl)
tyConToIfaceDecl TidyEnv
env TyCon
tycon
| Just Class
clas <- TyCon -> Maybe Class
tyConClass_maybe TyCon
tycon
= TidyEnv -> Class -> (TidyEnv, IfaceDecl)
classToIfaceDecl TidyEnv
env Class
clas
| Just Type
syn_rhs <- TyCon -> Maybe Type
synTyConRhs_maybe TyCon
tycon
= ( TidyEnv
tc_env1
, IfaceSynonym :: Name
-> [Role]
-> [IfaceTyConBinder]
-> IfaceType
-> IfaceType
-> IfaceDecl
IfaceSynonym { ifName :: Name
ifName = TyCon -> Name
forall a. NamedThing a => a -> Name
getName TyCon
tycon,
ifRoles :: [Role]
ifRoles = TyCon -> [Role]
tyConRoles TyCon
tycon,
ifSynRhs :: IfaceType
ifSynRhs = Type -> IfaceType
if_syn_type Type
syn_rhs,
ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
if_binders,
ifResKind :: IfaceType
ifResKind = IfaceType
if_res_kind
})
| Just FamTyConFlav
fam_flav <- TyCon -> Maybe FamTyConFlav
famTyConFlav_maybe TyCon
tycon
= ( TidyEnv
tc_env1
, IfaceFamily :: Name
-> Maybe RuleName
-> [IfaceTyConBinder]
-> IfaceType
-> IfaceFamTyConFlav
-> Injectivity
-> IfaceDecl
IfaceFamily { ifName :: Name
ifName = TyCon -> Name
forall a. NamedThing a => a -> Name
getName TyCon
tycon,
ifResVar :: Maybe RuleName
ifResVar = Maybe RuleName
if_res_var,
ifFamFlav :: IfaceFamTyConFlav
ifFamFlav = FamTyConFlav -> IfaceFamTyConFlav
to_if_fam_flav FamTyConFlav
fam_flav,
ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
if_binders,
ifResKind :: IfaceType
ifResKind = IfaceType
if_res_kind,
ifFamInj :: Injectivity
ifFamInj = TyCon -> Injectivity
tyConInjectivityInfo TyCon
tycon
})
| TyCon -> Bool
isAlgTyCon TyCon
tycon
= ( TidyEnv
tc_env1
, IfaceData :: Name
-> [IfaceTyConBinder]
-> IfaceType
-> Maybe CType
-> [Role]
-> IfaceContext
-> IfaceConDecls
-> Bool
-> IfaceTyConParent
-> IfaceDecl
IfaceData { ifName :: Name
ifName = TyCon -> Name
forall a. NamedThing a => a -> Name
getName TyCon
tycon,
ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
if_binders,
ifResKind :: IfaceType
ifResKind = IfaceType
if_res_kind,
ifCType :: Maybe CType
ifCType = TyCon -> Maybe CType
tyConCType TyCon
tycon,
ifRoles :: [Role]
ifRoles = TyCon -> [Role]
tyConRoles TyCon
tycon,
ifCtxt :: IfaceContext
ifCtxt = TidyEnv -> [Type] -> IfaceContext
tidyToIfaceContext TidyEnv
tc_env1 (TyCon -> [Type]
tyConStupidTheta TyCon
tycon),
ifCons :: IfaceConDecls
ifCons = AlgTyConRhs -> IfaceConDecls
ifaceConDecls (TyCon -> AlgTyConRhs
algTyConRhs TyCon
tycon),
ifGadtSyntax :: Bool
ifGadtSyntax = TyCon -> Bool
isGadtSyntaxTyCon TyCon
tycon,
ifParent :: IfaceTyConParent
ifParent = IfaceTyConParent
parent })
| Bool
otherwise
= ( TidyEnv
env
, IfaceData :: Name
-> [IfaceTyConBinder]
-> IfaceType
-> Maybe CType
-> [Role]
-> IfaceContext
-> IfaceConDecls
-> Bool
-> IfaceTyConParent
-> IfaceDecl
IfaceData { ifName :: Name
ifName = TyCon -> Name
forall a. NamedThing a => a -> Name
getName TyCon
tycon,
ifBinders :: [IfaceTyConBinder]
ifBinders = [IfaceTyConBinder]
if_binders,
ifResKind :: IfaceType
ifResKind = IfaceType
if_res_kind,
ifCType :: Maybe CType
ifCType = Maybe CType
forall a. Maybe a
Nothing,
ifRoles :: [Role]
ifRoles = TyCon -> [Role]
tyConRoles TyCon
tycon,
ifCtxt :: IfaceContext
ifCtxt = [],
ifCons :: IfaceConDecls
ifCons = [IfaceConDecl] -> IfaceConDecls
IfDataTyCon [],
ifGadtSyntax :: Bool
ifGadtSyntax = Bool
False,
ifParent :: IfaceTyConParent
ifParent = IfaceTyConParent
IfNoParent })
where
(TidyEnv
tc_env1, [TyConBinder]
tc_binders) = TidyEnv -> [TyConBinder] -> (TidyEnv, [TyConBinder])
tidyTyConBinders TidyEnv
env (TyCon -> [TyConBinder]
tyConBinders TyCon
tycon)
tc_tyvars :: [Id]
tc_tyvars = [TyConBinder] -> [Id]
forall tv argf. [VarBndr tv argf] -> [tv]
binderVars [TyConBinder]
tc_binders
if_binders :: [IfaceTyConBinder]
if_binders = [TyConBinder] -> [IfaceTyConBinder]
forall vis. [VarBndr Id vis] -> [VarBndr IfaceBndr vis]
toIfaceTyCoVarBinders [TyConBinder]
tc_binders
if_res_kind :: IfaceType
if_res_kind = TidyEnv -> Type -> IfaceType
tidyToIfaceType TidyEnv
tc_env1 (TyCon -> Type
tyConResKind TyCon
tycon)
if_syn_type :: Type -> IfaceType
if_syn_type Type
ty = TidyEnv -> Type -> IfaceType
tidyToIfaceType TidyEnv
tc_env1 Type
ty
if_res_var :: Maybe RuleName
if_res_var = Name -> RuleName
forall a. NamedThing a => a -> RuleName
getOccFS (Name -> RuleName) -> Maybe Name -> Maybe RuleName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` TyCon -> Maybe Name
tyConFamilyResVar_maybe TyCon
tycon
parent :: IfaceTyConParent
parent = case TyCon -> Maybe (TyCon, [Type], CoAxiom Unbranched)
tyConFamInstSig_maybe TyCon
tycon of
Just (TyCon
tc, [Type]
ty, CoAxiom Unbranched
ax) -> Name -> IfaceTyCon -> IfaceAppArgs -> IfaceTyConParent
IfDataInstance (CoAxiom Unbranched -> Name
forall (br :: BranchFlag). CoAxiom br -> Name
coAxiomName CoAxiom Unbranched
ax)
(TyCon -> IfaceTyCon
toIfaceTyCon TyCon
tc)
(TidyEnv -> TyCon -> [Type] -> IfaceAppArgs
tidyToIfaceTcArgs TidyEnv
tc_env1 TyCon
tc [Type]
ty)
Maybe (TyCon, [Type], CoAxiom Unbranched)
Nothing -> IfaceTyConParent
IfNoParent
to_if_fam_flav :: FamTyConFlav -> IfaceFamTyConFlav
to_if_fam_flav FamTyConFlav
OpenSynFamilyTyCon = IfaceFamTyConFlav
IfaceOpenSynFamilyTyCon
to_if_fam_flav FamTyConFlav
AbstractClosedSynFamilyTyCon = IfaceFamTyConFlav
IfaceAbstractClosedSynFamilyTyCon
to_if_fam_flav (DataFamilyTyCon {}) = IfaceFamTyConFlav
IfaceDataFamilyTyCon
to_if_fam_flav (BuiltInSynFamTyCon {}) = IfaceFamTyConFlav
IfaceBuiltInSynFamTyCon
to_if_fam_flav (ClosedSynFamilyTyCon Maybe (CoAxiom Branched)
Nothing) = Maybe (Name, [IfaceAxBranch]) -> IfaceFamTyConFlav
IfaceClosedSynFamilyTyCon Maybe (Name, [IfaceAxBranch])
forall a. Maybe a
Nothing
to_if_fam_flav (ClosedSynFamilyTyCon (Just CoAxiom Branched
ax))
= Maybe (Name, [IfaceAxBranch]) -> IfaceFamTyConFlav
IfaceClosedSynFamilyTyCon ((Name, [IfaceAxBranch]) -> Maybe (Name, [IfaceAxBranch])
forall a. a -> Maybe a
Just (Name
axn, [IfaceAxBranch]
ibr))
where defs :: [CoAxBranch]
defs = Branches Branched -> [CoAxBranch]
forall (br :: BranchFlag). Branches br -> [CoAxBranch]
fromBranches (Branches Branched -> [CoAxBranch])
-> Branches Branched -> [CoAxBranch]
forall a b. (a -> b) -> a -> b
$ CoAxiom Branched -> Branches Branched
forall (br :: BranchFlag). CoAxiom br -> Branches br
coAxiomBranches CoAxiom Branched
ax
lhss :: [[Type]]
lhss = (CoAxBranch -> [Type]) -> [CoAxBranch] -> [[Type]]
forall a b. (a -> b) -> [a] -> [b]
map CoAxBranch -> [Type]
coAxBranchLHS [CoAxBranch]
defs
ibr :: [IfaceAxBranch]
ibr = (CoAxBranch -> IfaceAxBranch) -> [CoAxBranch] -> [IfaceAxBranch]
forall a b. (a -> b) -> [a] -> [b]
map (TyCon -> [[Type]] -> CoAxBranch -> IfaceAxBranch
coAxBranchToIfaceBranch TyCon
tycon [[Type]]
lhss) [CoAxBranch]
defs
axn :: Name
axn = CoAxiom Branched -> Name
forall (br :: BranchFlag). CoAxiom br -> Name
coAxiomName CoAxiom Branched
ax
ifaceConDecls :: AlgTyConRhs -> IfaceConDecls
ifaceConDecls (NewTyCon { data_con :: AlgTyConRhs -> DataCon
data_con = DataCon
con }) = IfaceConDecl -> IfaceConDecls
IfNewTyCon (DataCon -> IfaceConDecl
ifaceConDecl DataCon
con)
ifaceConDecls (DataTyCon { data_cons :: AlgTyConRhs -> [DataCon]
data_cons = [DataCon]
cons }) = [IfaceConDecl] -> IfaceConDecls
IfDataTyCon ((DataCon -> IfaceConDecl) -> [DataCon] -> [IfaceConDecl]
forall a b. (a -> b) -> [a] -> [b]
map DataCon -> IfaceConDecl
ifaceConDecl [DataCon]
cons)
ifaceConDecls (TupleTyCon { data_con :: AlgTyConRhs -> DataCon
data_con = DataCon
con }) = [IfaceConDecl] -> IfaceConDecls
IfDataTyCon [DataCon -> IfaceConDecl
ifaceConDecl DataCon
con]
ifaceConDecls (SumTyCon { data_cons :: AlgTyConRhs -> [DataCon]
data_cons = [DataCon]
cons }) = [IfaceConDecl] -> IfaceConDecls
IfDataTyCon ((DataCon -> IfaceConDecl) -> [DataCon] -> [IfaceConDecl]
forall a b. (a -> b) -> [a] -> [b]
map DataCon -> IfaceConDecl
ifaceConDecl [DataCon]
cons)
ifaceConDecls AlgTyConRhs
AbstractTyCon = IfaceConDecls
IfAbstractTyCon
ifaceConDecl :: DataCon -> IfaceConDecl
ifaceConDecl DataCon
data_con
= IfCon :: Name
-> Bool
-> Bool
-> [IfaceBndr]
-> [IfaceForAllBndr]
-> [IfaceTvBndr]
-> IfaceContext
-> IfaceContext
-> [FieldLabel]
-> [IfaceBang]
-> [IfaceSrcBang]
-> IfaceConDecl
IfCon { ifConName :: Name
ifConName = DataCon -> Name
dataConName DataCon
data_con,
ifConInfix :: Bool
ifConInfix = DataCon -> Bool
dataConIsInfix DataCon
data_con,
ifConWrapper :: Bool
ifConWrapper = Maybe Id -> Bool
forall a. Maybe a -> Bool
isJust (DataCon -> Maybe Id
dataConWrapId_maybe DataCon
data_con),
ifConExTCvs :: [IfaceBndr]
ifConExTCvs = (Id -> IfaceBndr) -> [Id] -> [IfaceBndr]
forall a b. (a -> b) -> [a] -> [b]
map Id -> IfaceBndr
toIfaceBndr [Id]
ex_tvs',
ifConUserTvBinders :: [IfaceForAllBndr]
ifConUserTvBinders = (TyCoVarBinder -> IfaceForAllBndr)
-> [TyCoVarBinder] -> [IfaceForAllBndr]
forall a b. (a -> b) -> [a] -> [b]
map TyCoVarBinder -> IfaceForAllBndr
toIfaceForAllBndr [TyCoVarBinder]
user_bndrs',
ifConEqSpec :: [IfaceTvBndr]
ifConEqSpec = (EqSpec -> IfaceTvBndr) -> [EqSpec] -> [IfaceTvBndr]
forall a b. (a -> b) -> [a] -> [b]
map ((Id, Type) -> IfaceTvBndr
to_eq_spec ((Id, Type) -> IfaceTvBndr)
-> (EqSpec -> (Id, Type)) -> EqSpec -> IfaceTvBndr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EqSpec -> (Id, Type)
eqSpecPair) [EqSpec]
eq_spec,
ifConCtxt :: IfaceContext
ifConCtxt = TidyEnv -> [Type] -> IfaceContext
tidyToIfaceContext TidyEnv
con_env2 [Type]
theta,
ifConArgTys :: IfaceContext
ifConArgTys = (Type -> IfaceType) -> [Type] -> IfaceContext
forall a b. (a -> b) -> [a] -> [b]
map (TidyEnv -> Type -> IfaceType
tidyToIfaceType TidyEnv
con_env2) [Type]
arg_tys,
ifConFields :: [FieldLabel]
ifConFields = DataCon -> [FieldLabel]
dataConFieldLabels DataCon
data_con,
ifConStricts :: [IfaceBang]
ifConStricts = (HsImplBang -> IfaceBang) -> [HsImplBang] -> [IfaceBang]
forall a b. (a -> b) -> [a] -> [b]
map (TidyEnv -> HsImplBang -> IfaceBang
toIfaceBang TidyEnv
con_env2)
(DataCon -> [HsImplBang]
dataConImplBangs DataCon
data_con),
ifConSrcStricts :: [IfaceSrcBang]
ifConSrcStricts = (HsSrcBang -> IfaceSrcBang) -> [HsSrcBang] -> [IfaceSrcBang]
forall a b. (a -> b) -> [a] -> [b]
map HsSrcBang -> IfaceSrcBang
toIfaceSrcBang
(DataCon -> [HsSrcBang]
dataConSrcBangs DataCon
data_con)}
where
([Id]
univ_tvs, [Id]
ex_tvs, [EqSpec]
eq_spec, [Type]
theta, [Type]
arg_tys, Type
_)
= DataCon -> ([Id], [Id], [EqSpec], [Type], [Type], Type)
dataConFullSig DataCon
data_con
user_bndrs :: [TyCoVarBinder]
user_bndrs = DataCon -> [TyCoVarBinder]
dataConUserTyVarBinders DataCon
data_con
con_env1 :: TidyEnv
con_env1 = (TidyEnv -> TidyOccEnv
forall a b. (a, b) -> a
fst TidyEnv
tc_env1, [(Id, Id)] -> VarEnv Id
forall a. [(Id, a)] -> VarEnv a
mkVarEnv (String -> [Id] -> [Id] -> [(Id, Id)]
forall a b. String -> [a] -> [b] -> [(a, b)]
zipEqual String
"ifaceConDecl" [Id]
univ_tvs [Id]
tc_tyvars))
(TidyEnv
con_env2, [Id]
ex_tvs') = TidyEnv -> [Id] -> (TidyEnv, [Id])
tidyVarBndrs TidyEnv
con_env1 [Id]
ex_tvs
user_bndrs' :: [TyCoVarBinder]
user_bndrs' = (TyCoVarBinder -> TyCoVarBinder)
-> [TyCoVarBinder] -> [TyCoVarBinder]
forall a b. (a -> b) -> [a] -> [b]
map (TidyEnv -> TyCoVarBinder -> TyCoVarBinder
tidyUserTyCoVarBinder TidyEnv
con_env2) [TyCoVarBinder]
user_bndrs
to_eq_spec :: (Id, Type) -> IfaceTvBndr
to_eq_spec (Id
tv,Type
ty) = (TidyEnv -> Id -> RuleName
tidyTyVar TidyEnv
con_env2 Id
tv, TidyEnv -> Type -> IfaceType
tidyToIfaceType TidyEnv
con_env2 Type
ty)
tidyUserTyCoVarBinder :: TidyEnv -> TyCoVarBinder -> TyCoVarBinder
tidyUserTyCoVarBinder :: TidyEnv -> TyCoVarBinder -> TyCoVarBinder
tidyUserTyCoVarBinder TidyEnv
env (Bndr Id
tv ArgFlag
vis) =
Id -> ArgFlag -> TyCoVarBinder
forall var argf. var -> argf -> VarBndr var argf
Bndr (TidyEnv -> Id -> Id
tidyTyCoVarOcc TidyEnv
env Id
tv) ArgFlag
vis
classToIfaceDecl :: TidyEnv -> Class -> (TidyEnv, IfaceDecl)
classToIfaceDecl :: TidyEnv -> Class -> (TidyEnv, IfaceDecl)
classToIfaceDecl TidyEnv
env Class
clas
= ( TidyEnv
env1
, IfaceClass :: Name
-> [Role]
-> [IfaceTyConBinder]
-> [FunDep RuleName]
-> IfaceClassBody
-> IfaceDecl
IfaceClass { ifName :: Name
ifName = TyCon -> Name
forall a. NamedThing a => a -> Name
getName TyCon
tycon,
ifRoles :: [Role]
ifRoles = TyCon -> [Role]
tyConRoles (Class -> TyCon
classTyCon Class
clas),
ifBinders :: [IfaceTyConBinder]
ifBinders = [TyConBinder] -> [IfaceTyConBinder]
forall vis. [VarBndr Id vis] -> [VarBndr IfaceBndr vis]
toIfaceTyCoVarBinders [TyConBinder]
tc_binders,
ifBody :: IfaceClassBody
ifBody = IfaceClassBody
body,
ifFDs :: [FunDep RuleName]
ifFDs = (([Id], [Id]) -> FunDep RuleName)
-> [([Id], [Id])] -> [FunDep RuleName]
forall a b. (a -> b) -> [a] -> [b]
map ([Id], [Id]) -> FunDep RuleName
toIfaceFD [([Id], [Id])]
clas_fds })
where
([Id]
_, [([Id], [Id])]
clas_fds, [Type]
sc_theta, [Id]
_, [ClassATItem]
clas_ats, [ClassOpItem]
op_stuff)
= Class
-> ([Id], [([Id], [Id])], [Type], [Id], [ClassATItem],
[ClassOpItem])
classExtraBigSig Class
clas
tycon :: TyCon
tycon = Class -> TyCon
classTyCon Class
clas
body :: IfaceClassBody
body | TyCon -> Bool
isAbstractTyCon TyCon
tycon = IfaceClassBody
IfAbstractClass
| Bool
otherwise
= IfConcreteClass :: IfaceContext
-> [IfaceAT]
-> [IfaceClassOp]
-> BooleanFormula RuleName
-> IfaceClassBody
IfConcreteClass {
ifClassCtxt :: IfaceContext
ifClassCtxt = TidyEnv -> [Type] -> IfaceContext
tidyToIfaceContext TidyEnv
env1 [Type]
sc_theta,
ifATs :: [IfaceAT]
ifATs = (ClassATItem -> IfaceAT) -> [ClassATItem] -> [IfaceAT]
forall a b. (a -> b) -> [a] -> [b]
map ClassATItem -> IfaceAT
toIfaceAT [ClassATItem]
clas_ats,
ifSigs :: [IfaceClassOp]
ifSigs = (ClassOpItem -> IfaceClassOp) -> [ClassOpItem] -> [IfaceClassOp]
forall a b. (a -> b) -> [a] -> [b]
map ClassOpItem -> IfaceClassOp
toIfaceClassOp [ClassOpItem]
op_stuff,
ifMinDef :: BooleanFormula RuleName
ifMinDef = (Name -> RuleName)
-> BooleanFormula Name -> BooleanFormula RuleName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Name -> RuleName
forall a. NamedThing a => a -> RuleName
getOccFS (Class -> BooleanFormula Name
classMinimalDef Class
clas)
}
(TidyEnv
env1, [TyConBinder]
tc_binders) = TidyEnv -> [TyConBinder] -> (TidyEnv, [TyConBinder])
tidyTyConBinders TidyEnv
env (TyCon -> [TyConBinder]
tyConBinders TyCon
tycon)
toIfaceAT :: ClassATItem -> IfaceAT
toIfaceAT :: ClassATItem -> IfaceAT
toIfaceAT (ATI TyCon
tc Maybe (Type, SrcSpan)
def)
= IfaceDecl -> Maybe IfaceType -> IfaceAT
IfaceAT IfaceDecl
if_decl (((Type, SrcSpan) -> IfaceType)
-> Maybe (Type, SrcSpan) -> Maybe IfaceType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TidyEnv -> Type -> IfaceType
tidyToIfaceType TidyEnv
env2 (Type -> IfaceType)
-> ((Type, SrcSpan) -> Type) -> (Type, SrcSpan) -> IfaceType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Type, SrcSpan) -> Type
forall a b. (a, b) -> a
fst) Maybe (Type, SrcSpan)
def)
where
(TidyEnv
env2, IfaceDecl
if_decl) = TidyEnv -> TyCon -> (TidyEnv, IfaceDecl)
tyConToIfaceDecl TidyEnv
env1 TyCon
tc
toIfaceClassOp :: ClassOpItem -> IfaceClassOp
toIfaceClassOp (Id
sel_id, Maybe (Name, DefMethSpec Type)
def_meth)
= ASSERT( sel_tyvars == binderVars tc_binders )
Name -> IfaceType -> Maybe (DefMethSpec IfaceType) -> IfaceClassOp
IfaceClassOp (Id -> Name
forall a. NamedThing a => a -> Name
getName Id
sel_id)
(TidyEnv -> Type -> IfaceType
tidyToIfaceType TidyEnv
env1 Type
op_ty)
(((Name, DefMethSpec Type) -> DefMethSpec IfaceType)
-> Maybe (Name, DefMethSpec Type) -> Maybe (DefMethSpec IfaceType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Name, DefMethSpec Type) -> DefMethSpec IfaceType
toDmSpec Maybe (Name, DefMethSpec Type)
def_meth)
where
([Id]
sel_tyvars, Type
rho_ty) = Type -> ([Id], Type)
splitForAllTys (Id -> Type
idType Id
sel_id)
op_ty :: Type
op_ty = Type -> Type
funResultTy Type
rho_ty
toDmSpec :: (Name, DefMethSpec Type) -> DefMethSpec IfaceType
toDmSpec :: (Name, DefMethSpec Type) -> DefMethSpec IfaceType
toDmSpec (Name
_, DefMethSpec Type
VanillaDM) = DefMethSpec IfaceType
forall ty. DefMethSpec ty
VanillaDM
toDmSpec (Name
_, GenericDM Type
dm_ty) = IfaceType -> DefMethSpec IfaceType
forall ty. ty -> DefMethSpec ty
GenericDM (TidyEnv -> Type -> IfaceType
tidyToIfaceType TidyEnv
env1 Type
dm_ty)
toIfaceFD :: ([Id], [Id]) -> FunDep RuleName
toIfaceFD ([Id]
tvs1, [Id]
tvs2) = ((Id -> RuleName) -> [Id] -> [RuleName]
forall a b. (a -> b) -> [a] -> [b]
map (TidyEnv -> Id -> RuleName
tidyTyVar TidyEnv
env1) [Id]
tvs1
,(Id -> RuleName) -> [Id] -> [RuleName]
forall a b. (a -> b) -> [a] -> [b]
map (TidyEnv -> Id -> RuleName
tidyTyVar TidyEnv
env1) [Id]
tvs2)
tidyTyConBinder :: TidyEnv -> TyConBinder -> (TidyEnv, TyConBinder)
tidyTyConBinder :: TidyEnv -> TyConBinder -> (TidyEnv, TyConBinder)
tidyTyConBinder env :: TidyEnv
env@(TidyOccEnv
_, VarEnv Id
subst) tvb :: TyConBinder
tvb@(Bndr Id
tv TyConBndrVis
vis)
= case VarEnv Id -> Id -> Maybe Id
forall a. VarEnv a -> Id -> Maybe a
lookupVarEnv VarEnv Id
subst Id
tv of
Just Id
tv' -> (TidyEnv
env, Id -> TyConBndrVis -> TyConBinder
forall var argf. var -> argf -> VarBndr var argf
Bndr Id
tv' TyConBndrVis
vis)
Maybe Id
Nothing -> TidyEnv -> TyConBinder -> (TidyEnv, TyConBinder)
forall vis. TidyEnv -> VarBndr Id vis -> (TidyEnv, VarBndr Id vis)
tidyTyCoVarBinder TidyEnv
env TyConBinder
tvb
tidyTyConBinders :: TidyEnv -> [TyConBinder] -> (TidyEnv, [TyConBinder])
tidyTyConBinders :: TidyEnv -> [TyConBinder] -> (TidyEnv, [TyConBinder])
tidyTyConBinders = (TidyEnv -> TyConBinder -> (TidyEnv, TyConBinder))
-> TidyEnv -> [TyConBinder] -> (TidyEnv, [TyConBinder])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumL TidyEnv -> TyConBinder -> (TidyEnv, TyConBinder)
tidyTyConBinder
tidyTyVar :: TidyEnv -> TyVar -> FastString
tidyTyVar :: TidyEnv -> Id -> RuleName
tidyTyVar (TidyOccEnv
_, VarEnv Id
subst) Id
tv = Id -> RuleName
toIfaceTyVar (VarEnv Id -> Id -> Maybe Id
forall a. VarEnv a -> Id -> Maybe a
lookupVarEnv VarEnv Id
subst Id
tv Maybe Id -> Id -> Id
forall a. Maybe a -> a -> a
`orElse` Id
tv)
instanceToIfaceInst :: ClsInst -> IfaceClsInst
instanceToIfaceInst :: ClsInst -> IfaceClsInst
instanceToIfaceInst (ClsInst { is_dfun :: ClsInst -> Id
is_dfun = Id
dfun_id, is_flag :: ClsInst -> OverlapFlag
is_flag = OverlapFlag
oflag
, is_cls_nm :: ClsInst -> Name
is_cls_nm = Name
cls_name, is_cls :: ClsInst -> Class
is_cls = Class
cls
, is_tcs :: ClsInst -> [Maybe Name]
is_tcs = [Maybe Name]
mb_tcs
, is_orphan :: ClsInst -> IsOrphan
is_orphan = IsOrphan
orph })
= ASSERT( cls_name == className cls )
IfaceClsInst :: Name
-> [Maybe IfaceTyCon]
-> Name
-> OverlapFlag
-> IsOrphan
-> IfaceClsInst
IfaceClsInst { ifDFun :: Name
ifDFun = Name
dfun_name,
ifOFlag :: OverlapFlag
ifOFlag = OverlapFlag
oflag,
ifInstCls :: Name
ifInstCls = Name
cls_name,
ifInstTys :: [Maybe IfaceTyCon]
ifInstTys = (Maybe Name -> Maybe IfaceTyCon)
-> [Maybe Name] -> [Maybe IfaceTyCon]
forall a b. (a -> b) -> [a] -> [b]
map Maybe Name -> Maybe IfaceTyCon
do_rough [Maybe Name]
mb_tcs,
ifInstOrph :: IsOrphan
ifInstOrph = IsOrphan
orph }
where
do_rough :: Maybe Name -> Maybe IfaceTyCon
do_rough Maybe Name
Nothing = Maybe IfaceTyCon
forall a. Maybe a
Nothing
do_rough (Just Name
n) = IfaceTyCon -> Maybe IfaceTyCon
forall a. a -> Maybe a
Just (Name -> IfaceTyCon
toIfaceTyCon_name Name
n)
dfun_name :: Name
dfun_name = Id -> Name
idName Id
dfun_id
famInstToIfaceFamInst :: FamInst -> IfaceFamInst
famInstToIfaceFamInst :: FamInst -> IfaceFamInst
famInstToIfaceFamInst (FamInst { fi_axiom :: FamInst -> CoAxiom Unbranched
fi_axiom = CoAxiom Unbranched
axiom,
fi_fam :: FamInst -> Name
fi_fam = Name
fam,
fi_tcs :: FamInst -> [Maybe Name]
fi_tcs = [Maybe Name]
roughs })
= IfaceFamInst :: Name -> [Maybe IfaceTyCon] -> Name -> IsOrphan -> IfaceFamInst
IfaceFamInst { ifFamInstAxiom :: Name
ifFamInstAxiom = CoAxiom Unbranched -> Name
forall (br :: BranchFlag). CoAxiom br -> Name
coAxiomName CoAxiom Unbranched
axiom
, ifFamInstFam :: Name
ifFamInstFam = Name
fam
, ifFamInstTys :: [Maybe IfaceTyCon]
ifFamInstTys = (Maybe Name -> Maybe IfaceTyCon)
-> [Maybe Name] -> [Maybe IfaceTyCon]
forall a b. (a -> b) -> [a] -> [b]
map Maybe Name -> Maybe IfaceTyCon
do_rough [Maybe Name]
roughs
, ifFamInstOrph :: IsOrphan
ifFamInstOrph = IsOrphan
orph }
where
do_rough :: Maybe Name -> Maybe IfaceTyCon
do_rough Maybe Name
Nothing = Maybe IfaceTyCon
forall a. Maybe a
Nothing
do_rough (Just Name
n) = IfaceTyCon -> Maybe IfaceTyCon
forall a. a -> Maybe a
Just (Name -> IfaceTyCon
toIfaceTyCon_name Name
n)
fam_decl :: Name
fam_decl = TyCon -> Name
tyConName (TyCon -> Name) -> TyCon -> Name
forall a b. (a -> b) -> a -> b
$ CoAxiom Unbranched -> TyCon
forall (br :: BranchFlag). CoAxiom br -> TyCon
coAxiomTyCon CoAxiom Unbranched
axiom
mod :: Module
mod = ASSERT( isExternalName (coAxiomName axiom) )
HasDebugCallStack => Name -> Module
Name -> Module
nameModule (CoAxiom Unbranched -> Name
forall (br :: BranchFlag). CoAxiom br -> Name
coAxiomName CoAxiom Unbranched
axiom)
is_local :: Name -> Bool
is_local Name
name = Module -> Name -> Bool
nameIsLocalOrFrom Module
mod Name
name
lhs_names :: NameSet
lhs_names = (Name -> Bool) -> NameSet -> NameSet
filterNameSet Name -> Bool
is_local (CoAxiom Unbranched -> NameSet
forall (br :: BranchFlag). CoAxiom br -> NameSet
orphNamesOfCoCon CoAxiom Unbranched
axiom)
orph :: IsOrphan
orph | Name -> Bool
is_local Name
fam_decl
= OccName -> IsOrphan
NotOrphan (Name -> OccName
nameOccName Name
fam_decl)
| Bool
otherwise
= NameSet -> IsOrphan
chooseOrphanAnchor NameSet
lhs_names
coreRuleToIfaceRule :: CoreRule -> IfaceRule
coreRuleToIfaceRule :: CoreRule -> IfaceRule
coreRuleToIfaceRule (BuiltinRule { ru_fn :: CoreRule -> Name
ru_fn = Name
fn})
= String -> SDoc -> IfaceRule -> IfaceRule
forall a. String -> SDoc -> a -> a
pprTrace String
"toHsRule: builtin" (Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
fn) (IfaceRule -> IfaceRule) -> IfaceRule -> IfaceRule
forall a b. (a -> b) -> a -> b
$
Name -> IfaceRule
bogusIfaceRule Name
fn
coreRuleToIfaceRule (Rule { ru_name :: CoreRule -> RuleName
ru_name = RuleName
name, ru_fn :: CoreRule -> Name
ru_fn = Name
fn,
ru_act :: CoreRule -> Activation
ru_act = Activation
act, ru_bndrs :: CoreRule -> [Id]
ru_bndrs = [Id]
bndrs,
ru_args :: CoreRule -> [CoreExpr]
ru_args = [CoreExpr]
args, ru_rhs :: CoreRule -> CoreExpr
ru_rhs = CoreExpr
rhs,
ru_orphan :: CoreRule -> IsOrphan
ru_orphan = IsOrphan
orph, ru_auto :: CoreRule -> Bool
ru_auto = Bool
auto })
= IfaceRule :: RuleName
-> Activation
-> [IfaceBndr]
-> Name
-> [IfaceExpr]
-> IfaceExpr
-> Bool
-> IsOrphan
-> IfaceRule
IfaceRule { ifRuleName :: RuleName
ifRuleName = RuleName
name, ifActivation :: Activation
ifActivation = Activation
act,
ifRuleBndrs :: [IfaceBndr]
ifRuleBndrs = (Id -> IfaceBndr) -> [Id] -> [IfaceBndr]
forall a b. (a -> b) -> [a] -> [b]
map Id -> IfaceBndr
toIfaceBndr [Id]
bndrs,
ifRuleHead :: Name
ifRuleHead = Name
fn,
ifRuleArgs :: [IfaceExpr]
ifRuleArgs = (CoreExpr -> IfaceExpr) -> [CoreExpr] -> [IfaceExpr]
forall a b. (a -> b) -> [a] -> [b]
map CoreExpr -> IfaceExpr
do_arg [CoreExpr]
args,
ifRuleRhs :: IfaceExpr
ifRuleRhs = CoreExpr -> IfaceExpr
toIfaceExpr CoreExpr
rhs,
ifRuleAuto :: Bool
ifRuleAuto = Bool
auto,
ifRuleOrph :: IsOrphan
ifRuleOrph = IsOrphan
orph }
where
do_arg :: CoreExpr -> IfaceExpr
do_arg (Type Type
ty) = IfaceType -> IfaceExpr
IfaceType (Type -> IfaceType
toIfaceType (Type -> Type
deNoteType Type
ty))
do_arg (Coercion Coercion
co) = IfaceCoercion -> IfaceExpr
IfaceCo (Coercion -> IfaceCoercion
toIfaceCoercion Coercion
co)
do_arg CoreExpr
arg = CoreExpr -> IfaceExpr
toIfaceExpr CoreExpr
arg
bogusIfaceRule :: Name -> IfaceRule
bogusIfaceRule :: Name -> IfaceRule
bogusIfaceRule Name
id_name
= IfaceRule :: RuleName
-> Activation
-> [IfaceBndr]
-> Name
-> [IfaceExpr]
-> IfaceExpr
-> Bool
-> IsOrphan
-> IfaceRule
IfaceRule { ifRuleName :: RuleName
ifRuleName = String -> RuleName
fsLit String
"bogus", ifActivation :: Activation
ifActivation = Activation
NeverActive,
ifRuleBndrs :: [IfaceBndr]
ifRuleBndrs = [], ifRuleHead :: Name
ifRuleHead = Name
id_name, ifRuleArgs :: [IfaceExpr]
ifRuleArgs = [],
ifRuleRhs :: IfaceExpr
ifRuleRhs = Name -> IfaceExpr
IfaceExt Name
id_name, ifRuleOrph :: IsOrphan
ifRuleOrph = IsOrphan
IsOrphan,
ifRuleAuto :: Bool
ifRuleAuto = Bool
True }