{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiWayIf #-}
module GHC.Iface.Recomp
( checkOldIface
, RecompileRequired(..)
, recompileRequired
, addFingerprints
)
where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Driver.Backend
import GHC.Driver.Env
import GHC.Driver.Session
import GHC.Driver.Ppr
import GHC.Driver.Plugins ( PluginRecompile(..), PluginWithArgs(..), pluginRecompile', plugins )
import GHC.Iface.Syntax
import GHC.Iface.Recomp.Binary
import GHC.Iface.Load
import GHC.Iface.Recomp.Flags
import GHC.Core
import GHC.Tc.Utils.Monad
import GHC.Hs
import GHC.Data.Graph.Directed
import GHC.Data.Maybe
import GHC.Data.FastString
import GHC.Utils.Error
import GHC.Utils.Panic
import GHC.Utils.Outputable as Outputable
import GHC.Utils.Misc as Utils hiding ( eqListBy )
import GHC.Utils.Binary
import GHC.Utils.Fingerprint
import GHC.Utils.Exception
import GHC.Types.Annotations
import GHC.Types.Name
import GHC.Types.Name.Set
import GHC.Types.SrcLoc
import GHC.Types.Unique
import GHC.Types.Unique.Set
import GHC.Types.Fixity.Env
import GHC.Types.SourceFile
import GHC.Unit.External
import GHC.Unit.Finder
import GHC.Unit.State
import GHC.Unit.Home
import GHC.Unit.Module
import GHC.Unit.Module.ModIface
import GHC.Unit.Module.ModSummary
import GHC.Unit.Module.Warnings
import GHC.Unit.Module.Deps
import Control.Monad
import Data.Function
import Data.List (find, sortBy, sort)
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Word (Word64)
import qualified Data.Semigroup
data RecompileRequired
= UpToDate
| MustCompile
| RecompBecause String
deriving RecompileRequired -> RecompileRequired -> Bool
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
let logger :: Logger
logger = HscEnv -> Logger
hsc_logger HscEnv
hsc_env
Logger -> DynFlags -> String -> IO ()
showPass Logger
logger DynFlags
dflags forall a b. (a -> b) -> a -> b
$
String
"Checking old interface for " forall a. [a] -> [a] -> [a]
++
(forall a. Outputable a => DynFlags -> a -> String
showPpr DynFlags
dflags forall a b. (a -> b) -> a -> b
$ ModSummary -> Module
ms_mod ModSummary
mod_summary) forall a. [a] -> [a] -> [a]
++
String
" (use -ddump-hi-diffs for more details)"
forall a. SDoc -> HscEnv -> IfG a -> IO a
initIfaceCheck (String -> SDoc
text String
"checkOldIface") HscEnv
hsc_env 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 IfGblEnv ()) (Maybe ModIface)
getIface =
case Maybe ModIface
maybe_iface of
Just ModIface
_ -> do
forall m n. SDoc -> TcRnIf m n ()
traceIf (String -> SDoc
text String
"We already have the old interface for" SDoc -> SDoc -> SDoc
<+>
forall a. Outputable a => a -> SDoc
ppr (ModSummary -> Module
ms_mod ModSummary
mod_summary))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ModIface
maybe_iface
Maybe ModIface
Nothing -> IOEnv (Env IfGblEnv ()) (Maybe ModIface)
loadIface
loadIface :: IOEnv (Env IfGblEnv ()) (Maybe ModIface)
loadIface = do
let iface_path :: String
iface_path = ModSummary -> String
msHiFilePath ModSummary
mod_summary
MaybeErr SDoc ModIface
read_result <- 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
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)
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)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Succeeded ModIface
iface -> do
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)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ 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
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
src_changed forall a b. (a -> b) -> a -> b
$
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (Int -> SDoc -> SDoc
nest Int
4 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 (Backend -> Bool
backendProducesObject forall a b. (a -> b) -> a -> b
$ DynFlags -> Backend
backend DynFlags
dflags) ->
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)
getIface
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)
getIface
case Maybe ModIface
maybe_iface' of
Maybe ModIface
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
MustCompile, 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 { forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (String -> SDoc
text String
"Considering whether compilation is required for" SDoc -> SDoc -> SDoc
<+>
forall a. Outputable a => a -> SDoc
ppr (forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface) SDoc -> SDoc -> SDoc
<> SDoc
colon)
; if Bool -> Bool
not (HomeUnit -> Module -> Bool
isHomeModule HomeUnit
home_unit (forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface))
then forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
"-this-unit-id changed", 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 forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, 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 forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, 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 forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, 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 forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, 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 forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, forall a. Maybe a
Nothing) else do {
; RecompileRequired
recomp <- ModSummary -> IfG RecompileRequired
checkHie ModSummary
mod_summary
; if RecompileRequired -> Bool
recompileRequired RecompileRequired
recomp then forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, 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 forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, 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 forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, forall a. Maybe a
Nothing) else do {
; forall gbl lcl.
(ExternalPackageState -> ExternalPackageState) -> TcRnIf gbl lcl ()
updateEps_ forall a b. (a -> b) -> a -> b
$ \ExternalPackageState
eps -> ExternalPackageState
eps { eps_is_boot :: ModuleNameEnv ModuleNameWithIsBoot
eps_is_boot = ModuleNameEnv ModuleNameWithIsBoot
mod_deps }
; RecompileRequired
recomp <- [IfG RecompileRequired] -> IfG RecompileRequired
checkList [Unit -> Usage -> IfG RecompileRequired
checkModUsage (HomeUnit -> Unit
homeUnitAsUnit HomeUnit
home_unit) Usage
u
| Usage
u <- forall (phase :: ModIfacePhase). ModIface_ phase -> [Usage]
mi_usages ModIface
iface]
; forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, forall a. a -> Maybe a
Just ModIface
iface)
}}}}}}}}}}
where
home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
mod_deps :: ModuleNameEnv ModuleNameWithIsBoot
mod_deps :: ModuleNameEnv ModuleNameWithIsBoot
mod_deps = [ModuleNameWithIsBoot] -> ModuleNameEnv ModuleNameWithIsBoot
mkModDeps (Dependencies -> [ModuleNameWithIsBoot]
dep_mods (forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface))
checkPlugins :: HscEnv -> ModIface -> IfG RecompileRequired
checkPlugins :: HscEnv -> ModIface -> IfG RecompileRequired
checkPlugins HscEnv
hsc_env ModIface
iface = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
Fingerprint
new_fingerprint <- HscEnv -> IO Fingerprint
fingerprintPlugins HscEnv
hsc_env
let old_fingerprint :: Fingerprint
old_fingerprint = ModIfaceBackend -> Fingerprint
mi_plugin_hash (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
PluginRecompile
pr <- forall a. Monoid a => [a] -> a
mconcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM PluginWithArgs -> IO PluginRecompile
pluginRecompile' (HscEnv -> [PluginWithArgs]
plugins HscEnv
hsc_env)
forall (m :: * -> *) a. Monad m => a -> m a
return 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 =
[PluginWithArgs] -> IO Fingerprint
fingerprintPlugins' forall a b. (a -> b) -> a -> b
$ HscEnv -> [PluginWithArgs]
plugins HscEnv
hsc_env
fingerprintPlugins' :: [PluginWithArgs] -> IO Fingerprint
fingerprintPlugins' :: [PluginWithArgs] -> IO Fingerprint
fingerprintPlugins' [PluginWithArgs]
plugins = do
PluginRecompile
res <- forall a. Monoid a => [a] -> a
mconcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM PluginWithArgs -> IO PluginRecompile
pluginRecompile' [PluginWithArgs]
plugins
forall (m :: * -> *) a. Monad m => a -> m a
return 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 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 forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Fingerprint]
magic_fingerprints Bool -> Bool -> Bool
||
Fingerprint
new_fp 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
HscEnv
hsc_env <- forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
let home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
outer_mod :: Module
outer_mod = ModSummary -> Module
ms_mod ModSummary
mod_summary
inner_mod :: Module
inner_mod = HomeUnit -> ModuleName -> Module
homeModuleNameInstantiation HomeUnit
home_unit (forall unit. GenModule unit -> ModuleName
moduleName Module
outer_mod)
MASSERT( isHomeModule home_unit outer_mod )
case Module
inner_mod forall a. Eq a => a -> a -> Bool
== 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 -> 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 <- 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
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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 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 (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
Fingerprint
new_hash <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> Module -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintDynFlags HscEnv
hsc_env
(forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module ModIface
iface)
BinHandle -> Name -> IO ()
putNameLiterally
case Fingerprint
old_hash 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 (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
Fingerprint
new_hash <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 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 (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
Fingerprint
new_hash <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO 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 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
UnitState
unit_state <- HscEnv -> UnitState
hsc_units forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall gbl lcl. TcRnIf gbl lcl HscEnv
getTopEnv
let old_merged :: [Module]
old_merged = forall a. Ord a => [a] -> [a]
sort [ Module
mod | UsageMergedRequirement{ usg_mod :: Usage -> Module
usg_mod = Module
mod } <- forall (phase :: ModIfacePhase). ModIface_ phase -> [Usage]
mi_usages ModIface
iface ]
new_merged :: [Module]
new_merged = case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (ModSummary -> ModuleName
ms_mod_name ModSummary
mod_summary)
(UnitState -> Map ModuleName [InstantiatedModule]
requirementContext UnitState
unit_state) of
Maybe [InstantiatedModule]
Nothing -> []
Just [InstantiatedModule]
r -> forall a. Ord a => [a] -> [a]
sort forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (UnitState -> InstantiatedModule -> Module
instModuleToModule UnitState
unit_state) [InstantiatedModule]
r
if [Module]
old_merged 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
$$ forall a. Outputable a => a -> SDoc
ppr [Module]
new_merged)
else 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
=
[IfG RecompileRequired] -> IfG RecompileRequired
checkList forall a b. (a -> b) -> a -> b
$
[ [IfG RecompileRequired] -> IfG RecompileRequired
checkList (forall a b. (a -> b) -> [a] -> [b]
map (Maybe FastString, GenLocated SrcSpan ModuleName)
-> IfG RecompileRequired
dep_missing (ModSummary -> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
ms_imps ModSummary
summary forall a. [a] -> [a] -> [a]
++ ModSummary -> [(Maybe FastString, GenLocated SrcSpan ModuleName)]
ms_srcimps ModSummary
summary))
, do
(RecompileRequired
recomp, [[ModuleName]]
mnames_seen) <- forall {m :: * -> *} {a}.
Monad m =>
[m (RecompileRequired, a)] -> m (RecompileRequired, [a])
runUntilRecompRequired forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map
GenLocated SrcSpan 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 = forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a
Set.unions forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. Ord a => [a] -> Set a
Set.fromList [[ModuleName]]
mnames_seen
Set ModuleName -> IfG RecompileRequired
checkIfAllOldHomeDependenciesAreSeen Set ModuleName
seen_home_deps
RecompileRequired
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recomp]
where
prev_dep_mods :: [ModuleNameWithIsBoot]
prev_dep_mods = Dependencies -> [ModuleNameWithIsBoot]
dep_mods (forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface)
prev_dep_plgn :: [ModuleName]
prev_dep_plgn = Dependencies -> [ModuleName]
dep_plgins (forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface)
prev_dep_pkgs :: [(UnitId, Bool)]
prev_dep_pkgs = Dependencies -> [(UnitId, Bool)]
dep_pkgs (forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
iface)
home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit HscEnv
hsc_env
dep_missing :: (Maybe FastString, GenLocated SrcSpan ModuleName)
-> IfG RecompileRequired
dep_missing (Maybe FastString
mb_pkg, L SrcSpan
_ ModuleName
mod) = do
FindResult
find_res <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
findImportedModule HscEnv
hsc_env ModuleName
mod (Maybe FastString
mb_pkg)
let reason :: String
reason = ModuleName -> String
moduleNameString ModuleName
mod forall a. [a] -> [a] -> [a]
++ String
" changed"
case FindResult
find_res of
Found ModLocation
_ Module
mod
| HomeUnit -> Unit -> Bool
isHomeUnit HomeUnit
home_unit Unit
pkg
-> if forall unit. GenModule unit -> ModuleName
moduleName Module
mod forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` forall a b. (a -> b) -> [a] -> [b]
map forall mod. GenWithIsBoot mod -> mod
gwib_mod [ModuleNameWithIsBoot]
prev_dep_mods forall a. [a] -> [a] -> [a]
++ [ModuleName]
prev_dep_plgn
then do forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"imported module " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr Module
mod) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
" not among previous dependencies"
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
reason)
else
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
| Bool
otherwise
-> if Unit -> UnitId
toUnitId Unit
pkg forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(UnitId, Bool)]
prev_dep_pkgs)
then do forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"imported module " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (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 (forall a. Outputable a => a -> SDoc
ppr Unit
pkg) SDoc -> SDoc -> SDoc
<>
String -> SDoc
text String
", which is not among previous dependencies"
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
reason)
else
forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
where pkg :: Unit
pkg = forall unit. GenModule unit -> unit
moduleUnit Module
mod
FindResult
_otherwise -> forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
reason)
projectNonBootNames :: [GenWithIsBoot b] -> [b]
projectNonBootNames = forall a b. (a -> b) -> [a] -> [b]
map forall mod. GenWithIsBoot mod -> mod
gwib_mod forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
== IsBootInterface
NotBoot) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall mod. GenWithIsBoot mod -> IsBootInterface
gwib_isBoot)
old_deps :: Set ModuleName
old_deps = forall a. Ord a => [a] -> Set a
Set.fromList
forall a b. (a -> b) -> a -> b
$ forall {b}. [GenWithIsBoot b] -> [b]
projectNonBootNames [ModuleNameWithIsBoot]
prev_dep_mods
isOldHomeDeps :: ModuleName -> Bool
isOldHomeDeps = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Ord a => a -> Set a -> Bool
Set.member Set ModuleName
old_deps
checkForNewHomeDependency :: GenLocated SrcSpan ModuleName
-> IOEnv (Env IfGblEnv ()) (RecompileRequired, [ModuleName])
checkForNewHomeDependency (L SrcSpan
_ ModuleName
mname) = do
let
mod :: Module
mod = HomeUnit -> ModuleName -> Module
mkHomeModule HomeUnit
home_unit ModuleName
mname
str_mname :: String
str_mname = ModuleName -> String
moduleNameString ModuleName
mname
reason :: String
reason = String
str_mname forall a. [a] -> [a] -> [a]
++ String
" changed"
if Bool -> Bool
not (ModuleName -> Bool
isOldHomeDeps ModuleName
mname)
then forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
UpToDate, [])
else do
Maybe (RecompileRequired, [ModuleName])
mb_result <- forall a. String -> Module -> (ModIface -> IfG a) -> IfG (Maybe a)
getFromModIface String
"need mi_deps for" Module
mod forall a b. (a -> b) -> a -> b
$ \ModIface
imported_iface -> do
let mnames :: [ModuleName]
mnames = ModuleName
mnameforall a. a -> [a] -> [a]
:(forall a b. (a -> b) -> [a] -> [b]
map forall mod. GenWithIsBoot mod -> mod
gwib_mod forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
== IsBootInterface
NotBoot) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall mod. GenWithIsBoot mod -> IsBootInterface
gwib_isBoot) forall a b. (a -> b) -> a -> b
$
Dependencies -> [ModuleNameWithIsBoot]
dep_mods forall a b. (a -> b) -> a -> b
$ forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps ModIface
imported_iface)
case forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleName -> Bool
isOldHomeDeps) [ModuleName]
mnames of
Maybe ModuleName
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
UpToDate, [ModuleName]
mnames)
Just ModuleName
new_dep_mname -> do
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"imported home module " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (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 (forall a. Outputable a => a -> SDoc
ppr ModuleName
new_dep_mname)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> RecompileRequired
RecompBecause String
reason, [])
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe (RecompileRequired
MustCompile, []) Maybe (RecompileRequired, [ModuleName])
mb_result
runUntilRecompRequired :: [m (RecompileRequired, a)] -> m (RecompileRequired, [a])
runUntilRecompRequired [] = 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 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
forall (m :: * -> *) a. Monad m => a -> m a
return (RecompileRequired
recomp, a
valueforall a. a -> [a] -> [a]
:[a]
values)
checkIfAllOldHomeDependenciesAreSeen :: Set ModuleName -> IfG RecompileRequired
checkIfAllOldHomeDependenciesAreSeen Set ModuleName
seen_deps = do
let unseen_old_deps :: Set ModuleName
unseen_old_deps = forall a. Ord a => Set a -> Set a -> Set a
Set.difference
Set ModuleName
old_deps
Set ModuleName
seen_deps
if Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null Set ModuleName
unseen_old_deps)
then do
let missing_dep :: ModuleName
missing_dep = forall a. Int -> Set a -> a
Set.elemAt Int
0 Set ModuleName
unseen_old_deps
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs forall a b. (a -> b) -> a -> b
$
String -> SDoc
text String
"missing old home dependency " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
quotes (forall a. Outputable a => a -> SDoc
ppr ModuleName
missing_dep)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> RecompileRequired
RecompBecause String
"missing old dependency"
else 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 <- 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 -> forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
MustCompile
Just RecompileRequired
recomp -> forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recomp
getFromModIface :: String -> Module -> (ModIface -> IfG a)
-> IfG (Maybe a)
getFromModIface :: forall a. 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, forall a. Outputable a => a -> SDoc
ppr Module
mod]
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (String -> SDoc
text String
"Checking innterface for module" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr Module
mod)
MaybeErr SDoc ModIface
mb_iface <- 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
forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs ([SDoc] -> SDoc
sep [String -> SDoc
text String
"Couldn't load interface for module",
forall a. Outputable a => a -> SDoc
ppr Module
mod])
forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Succeeded ModIface
iface -> forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ModIface -> IfG a
getter ModIface
iface
checkModUsage :: Unit -> Usage -> IfG RecompileRequired
checkModUsage :: Unit -> Usage -> IfG RecompileRequired
checkModUsage Unit
_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 forall a b. (a -> b) -> a -> b
$ \ModIface
iface -> do
let reason :: String
reason = ModuleName -> String
moduleNameString (forall unit. GenModule unit -> ModuleName
moduleName Module
mod) forall a. [a] -> [a] -> [a]
++ String
" changed"
String -> Fingerprint -> Fingerprint -> IfG RecompileRequired
checkModuleFingerprint String
reason Fingerprint
old_mod_hash (ModIfaceBackend -> Fingerprint
mi_mod_hash (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface))
checkModUsage Unit
_ 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 forall a b. (a -> b) -> a -> b
$ \ModIface
iface -> do
let reason :: String
reason = ModuleName -> String
moduleNameString (forall unit. GenModule unit -> ModuleName
moduleName Module
mod) 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 (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface))
checkModUsage Unit
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 = forall u. u -> ModuleName -> GenModule u
mkModule Unit
this_pkg ModuleName
mod_name
Module
-> (ModIface -> IfG RecompileRequired) -> IfG RecompileRequired
needInterface Module
mod forall a b. (a -> b) -> a -> b
$ \ModIface
iface -> do
let
new_mod_hash :: Fingerprint
new_mod_hash = ModIfaceBackend -> Fingerprint
mi_mod_hash (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 (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
new_export_hash :: Fingerprint
new_export_hash = ModIfaceBackend -> Fingerprint
mi_exp_hash (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface)
reason :: String
reason = ModuleName -> String
moduleNameString ModuleName
mod_name 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 forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
else
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") 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 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 Unit
_this_pkg UsageFile{ usg_file_path :: Usage -> String
usg_file_path = String
file,
usg_file_hash :: Usage -> Fingerprint
usg_file_hash = Fingerprint
old_hash } =
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a. (IOException -> IO a) -> IO a -> IO a
handleIO IOException -> IO RecompileRequired
handler forall a b. (a -> b) -> a -> b
$ do
Fingerprint
new_hash <- String -> IO Fingerprint
getFileHash String
file
if (Fingerprint
old_hash forall a. Eq a => a -> a -> Bool
/= Fingerprint
new_hash)
then forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recomp
else forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
UpToDate
where
recomp :: RecompileRequired
recomp = String -> RecompileRequired
RecompBecause (String
file forall a. [a] -> [a] -> [a]
++ String
" changed")
handler :: IOException -> IO RecompileRequired
handler =
#if defined(DEBUG)
\e -> pprTrace "UsageFile" (text (show e)) $ return recomp
#else
\IOException
_ -> 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 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 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:", forall a. Outputable a => a -> SDoc
ppr OccName
name])
Just (OccName
_, Fingerprint
new_hash)
| Fingerprint
new_hash forall a. Eq a => a -> a -> Bool
== Fingerprint
old_hash -> do forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs (String -> SDoc
text String
" Up to date" SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr OccName
name SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (forall a. Outputable a => a -> SDoc
ppr Fingerprint
new_hash))
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
<+> 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 = forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs SDoc
msg forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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 = forall m n. SDoc -> TcRnIf m n ()
traceHiDiffs SDoc
msg forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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, forall a. Outputable a => a -> SDoc
ppr Fingerprint
old_hash, String -> SDoc
text String
"->", forall a. Outputable a => a -> SDoc
ppr Fingerprint
new_hash])
checkList :: [IfG RecompileRequired] -> IfG RecompileRequired
checkList :: [IfG RecompileRequired] -> IfG RecompileRequired
checkList [] = 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 forall (m :: * -> *) a. Monad m => a -> m a
return RecompileRequired
recompile
else [IfG RecompileRequired] -> IfG RecompileRequired
checkList [IfG RecompileRequired]
checks
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 = forall (phase :: ModIfacePhase).
ModIface_ phase -> [IfaceDeclExts phase]
mi_decls PartialModIface
iface0
warn_fn :: OccName -> Maybe WarningTxt
warn_fn = Warnings -> OccName -> Maybe WarningTxt
mkIfaceWarnCache (forall (phase :: ModIfacePhase). ModIface_ phase -> Warnings
mi_warns PartialModIface
iface0)
fix_fn :: OccName -> Maybe Fixity
fix_fn = [(OccName, Fixity)] -> OccName -> Maybe Fixity
mkIfaceFixCache (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 =
forall a. [(OccName, a)] -> OccEnv a
mkOccEnv [ (Name -> OccName
nameOccName Name
nm, Name
nm)
| IfaceId { ifName :: IfaceDecl -> Name
ifName = Name
nm } <- [IfaceDeclExts 'ModIfaceCore]
decls ]
edges :: [ Node Unique IfaceDeclABI ]
edges :: [Node Unique IfaceDeclABI]
edges = [ forall key payload. payload -> key -> [key] -> Node key payload
DigraphNode IfaceDeclABI
abi (forall a. Uniquable a => a -> Unique
getUnique (forall a. NamedThing a => a -> OccName
getOccName IfaceDecl
decl)) [Unique]
out
| IfaceDecl
decl <- [IfaceDeclExts 'ModIfaceCore]
decls
, let abi :: IfaceDeclABI
abi = IfaceDecl -> IfaceDeclABI
declABI IfaceDecl
decl
, let out :: [Unique]
out = UniqSet Name -> [Unique]
localOccs forall a b. (a -> b) -> a -> b
$ IfaceDeclABI -> UniqSet Name
freeNamesDeclABI IfaceDeclABI
abi
]
name_module :: Name -> Module
name_module Name
n = ASSERT2( isExternalName n, ppr n ) nameModule n
localOccs :: UniqSet Name -> [Unique]
localOccs =
forall a b. (a -> b) -> [a] -> [b]
map (forall a. Uniquable a => a -> Unique
getUnique forall b c a. (b -> c) -> (a -> b) -> a -> c
. OccName -> OccName
getParent forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. NamedThing a => a -> OccName
getOccName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
== Module
semantic_mod) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Module
name_module)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet
where getParent :: OccName -> OccName
getParent :: OccName -> OccName
getParent OccName
occ = forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv OccName
parent_map OccName
occ forall a. Maybe a -> a -> a
`orElse` OccName
occ
parent_map :: OccEnv OccName
parent_map :: OccEnv OccName
parent_map = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' OccEnv OccName -> IfaceDecl -> OccEnv OccName
extend forall a. OccEnv a
emptyOccEnv [IfaceDeclExts 'ModIfaceCore]
decls
where extend :: OccEnv OccName -> IfaceDecl -> OccEnv OccName
extend OccEnv OccName
env IfaceDecl
d =
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 = forall a. NamedThing a => a -> OccName
getOccName IfaceDecl
d
groups :: [SCC IfaceDeclABI]
groups :: [SCC IfaceDeclABI]
groups = 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
nameModule Name
name forall a. Eq a => a -> a -> Bool
/= Module
semantic_mod = Name -> IO Fingerprint
global_hash_fn Name
name
| Module
semantic_mod forall a. Eq a => a -> a -> Bool
/= Module
this_mod
, Bool -> Bool
not (forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
semantic_mod) = Name -> IO Fingerprint
global_hash_fn Name
name
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. (a, b) -> b
snd (forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv (OccName, Fingerprint)
local_env (forall a. NamedThing a => a -> OccName
getOccName Name
name)
forall a. Maybe a -> a -> a
`orElse` forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"urk! lookup local fingerprint"
(forall a. Outputable a => a -> SDoc
ppr Name
name SDoc -> SDoc -> SDoc
$$ forall a. Outputable a => a -> SDoc
ppr OccEnv (OccName, Fingerprint)
local_env)))
in IO Fingerprint
hash forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= 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 <- 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)
forall (m :: * -> *) a. Monad m => a -> m a
return (OccEnv (OccName, Fingerprint)
env', (Fingerprint
hash,IfaceDecl
decl) 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 stable_abis :: [IfaceDeclABI]
stable_abis = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy IfaceDeclABI -> IfaceDeclABI -> Ordering
cmp_abiNames [IfaceDeclABI]
abis
stable_decls :: [IfaceDecl]
stable_decls = forall a b. (a -> b) -> [a] -> [b]
map IfaceDeclABI -> IfaceDecl
abiDecl [IfaceDeclABI]
stable_abis
OccEnv (OccName, Fingerprint)
local_env1 <- 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
(forall a b. [a] -> [b] -> [(a, b)]
zip (forall a b. (a -> b) -> [a] -> [b]
map Word64 -> Fingerprint
mkRecFingerprint [Word64
0..]) [IfaceDecl]
stable_decls)
let hash_fn :: BinHandle -> Name -> IO ()
hash_fn = OccEnv (OccName, Fingerprint) -> BinHandle -> Name -> IO ()
mk_put_name OccEnv (OccName, Fingerprint)
local_env1
Fingerprint
hash <- forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
hash_fn [IfaceDeclABI]
stable_abis
let pairs :: [(Fingerprint, IfaceDecl)]
pairs = forall a b. [a] -> [b] -> [(a, b)]
zip (forall a b. (a -> b) -> [a] -> [b]
map (Fingerprint -> Word64 -> Fingerprint
bumpFingerprint Fingerprint
hash) [Word64
0..]) [IfaceDecl]
stable_decls
OccEnv (OccName, Fingerprint)
local_env2 <- 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
forall (m :: * -> *) a. Monad m => a -> m a
return (OccEnv (OccName, Fingerprint)
local_env2, [(Fingerprint, IfaceDecl)]
pairs forall a. [a] -> [a] -> [a]
++ [(Fingerprint, IfaceDecl)]
decls_w_hashes)
mkRecFingerprint :: Word64 -> Fingerprint
mkRecFingerprint :: Word64 -> Fingerprint
mkRecFingerprint Word64
i = Word64 -> Word64 -> Fingerprint
Fingerprint Word64
0 Word64
i
bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint
bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint
bumpFingerprint Fingerprint
fp Word64
n = [Fingerprint] -> Fingerprint
fingerprintFingerprints [ Fingerprint
fp, Word64 -> Fingerprint
mkRecFingerprint Word64
n ]
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) =
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\(OccName
b,Fingerprint
fp) OccEnv (OccName, Fingerprint)
env -> 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) <-
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 (forall a. OccEnv a
emptyOccEnv, []) [SCC IfaceDeclABI]
groups
let sorted_deps :: Dependencies
sorted_deps :: Dependencies
sorted_deps = Dependencies -> Dependencies
sortDependencies (forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps PartialModIface
iface0)
let orph_mods :: [Module]
orph_mods
= forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= Module
this_mod)
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 <- 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)
(forall a b. (a -> b) -> [a] -> [b]
map IfaceClsInst -> Name
ifDFun [IfaceClsInst]
orph_insts, [IfaceRule]
orph_rules, [IfaceFamInst]
orph_fis)
Fingerprint
export_hash <- forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
putNameLiterally
(forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceExport]
mi_exports PartialModIface
iface0,
Fingerprint
orphan_hash,
[Fingerprint]
dep_orphan_hashes,
Dependencies -> [(UnitId, Bool)]
dep_pkgs (forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps PartialModIface
iface0),
Dependencies -> [Module]
dep_finsts (forall (phase :: ModIfacePhase). ModIface_ phase -> Dependencies
mi_deps PartialModIface
iface0),
forall (phase :: ModIfacePhase). ModIface_ phase -> IfaceTrustInfo
mi_trust PartialModIface
iface0)
let sorted_decls :: [(Fingerprint, IfaceDecl)]
sorted_decls :: [(Fingerprint, IfaceDecl)]
sorted_decls = forall k a. Map k a -> [a]
Map.elems forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$
[(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 <- HscEnv -> Module -> (BinHandle -> Name -> IO ()) -> IO Fingerprint
fingerprintDynFlags HscEnv
hsc_env 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 <- forall a.
Binary a =>
(BinHandle -> Name -> IO ()) -> a -> IO Fingerprint
computeFingerprint BinHandle -> Name -> IO ()
putNameLiterally
(forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(Fingerprint, IfaceDecl)]
sorted_decls,
Fingerprint
export_hash,
forall (phase :: ModIfacePhase). ModIface_ phase -> Warnings
mi_warns PartialModIface
iface0)
Fingerprint
iface_hash <- 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"),
forall (phase :: ModIfacePhase). ModIface_ phase -> [Usage]
mi_usages PartialModIface
iface0,
Dependencies
sorted_deps,
forall (phase :: ModIfacePhase). ModIface_ phase -> Bool
mi_hpc PartialModIface
iface0)
let
final_iface_exts :: ModIfaceBackend
final_iface_exts = 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 ( forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all IfaceRule -> Bool
ifRuleAuto [IfaceRule]
orph_rules
Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IfaceClsInst]
orph_insts
Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Bool
null [IfaceFamInst]
orph_fis)
, mi_finsts :: Bool
mi_finsts = Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null (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 = 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)]
sorted_decls, mi_final_exts :: IfaceBackendExts 'ModIfaceFinal
mi_final_exts = ModIfaceBackend
final_iface_exts }
forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
final_iface
where
this_mod :: Module
this_mod = forall (phase :: ModIfacePhase). ModIface_ phase -> Module
mi_module PartialModIface
iface0
semantic_mod :: Module
semantic_mod = 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) = forall decl.
(decl -> IsOrphan) -> [decl] -> (OccEnv [decl], [decl])
mkOrphMap IfaceClsInst -> IsOrphan
ifInstOrph (forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceClsInst]
mi_insts PartialModIface
iface0)
(OccEnv [IfaceRule]
non_orph_rules, [IfaceRule]
orph_rules) = forall decl.
(decl -> IsOrphan) -> [decl] -> (OccEnv [decl], [decl])
mkOrphMap IfaceRule -> IsOrphan
ifRuleOrph (forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceRule]
mi_rules PartialModIface
iface0)
(OccEnv [IfaceFamInst]
non_orph_fis, [IfaceFamInst]
orph_fis) = forall decl.
(decl -> IsOrphan) -> [decl] -> (OccEnv [decl], [decl])
mkOrphMap IfaceFamInst -> IsOrphan
ifFamInstOrph (forall (phase :: ModIfacePhase). ModIface_ phase -> [IfaceFamInst]
mi_fam_insts PartialModIface
iface0)
ann_fn :: OccName -> [AnnPayload]
ann_fn = [IfaceAnnotation] -> OccName -> [AnnPayload]
mkIfaceAnnCache (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 -> forall (m :: * -> *) a. Monad m => a -> m a
return (ModIfaceBackend -> Fingerprint
mi_orphan_hash (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface))
Maybe ModIface
Nothing -> do
ModIface
iface <- forall a. HscEnv -> IfG a -> IO a
initIfaceLoad HscEnv
hsc_env forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall gbl lcl a.
TcRnIf gbl lcl (MaybeErr SDoc a) -> TcRnIf gbl lcl a
withException
forall a b. (a -> b) -> a -> b
$ forall lcl.
SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr SDoc ModIface)
loadInterface (String -> SDoc
text String
"getOrphanHashes") Module
mod WhereFrom
ImportBySystem
forall (m :: * -> *) a. Monad m => a -> m a
return (ModIfaceBackend -> Fingerprint
mi_orphan_hash (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface))
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 { dep_mods :: [ModuleNameWithIsBoot]
dep_mods = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (FastString -> FastString -> Ordering
lexicalCompareFS forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (ModuleName -> FastString
moduleNameFS forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall mod. GenWithIsBoot mod -> mod
gwib_mod)) (Dependencies -> [ModuleNameWithIsBoot]
dep_mods Dependencies
d),
dep_pkgs :: [(UnitId, Bool)]
dep_pkgs = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. (a, b) -> a
fst) (Dependencies -> [(UnitId, Bool)]
dep_pkgs Dependencies
d),
dep_orphs :: [Module]
dep_orphs = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Module -> Module -> Ordering
stableModuleCmp (Dependencies -> [Module]
dep_orphs Dependencies
d),
dep_finsts :: [Module]
dep_finsts = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy Module -> Module -> Ordering
stableModuleCmp (Dependencies -> [Module]
dep_finsts Dependencies
d),
dep_plgins :: [ModuleName]
dep_plgins = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (FastString -> FastString -> Ordering
lexicalCompareFS forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` ModuleName -> FastString
moduleNameFS) (Dependencies -> [ModuleName]
dep_plgins Dependencies
d) }
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 = forall a. NamedThing a => a -> OccName
getOccName (IfaceDeclABI -> IfaceDecl
abiDecl IfaceDeclABI
abi1) forall a. Ord a => a -> a -> Ordering
`compare`
forall a. NamedThing a => a -> OccName
getOccName (IfaceDeclABI -> IfaceDecl
abiDecl IfaceDeclABI
abi2)
freeNamesDeclABI :: IfaceDeclABI -> NameSet
freeNamesDeclABI :: IfaceDeclABI -> UniqSet Name
freeNamesDeclABI (Module
_mod, IfaceDecl
decl, IfaceDeclExtras
extras) =
IfaceDecl -> UniqSet Name
freeNamesIfDecl IfaceDecl
decl UniqSet Name -> UniqSet Name -> UniqSet Name
`unionNameSet` IfaceDeclExtras -> UniqSet Name
freeNamesDeclExtras IfaceDeclExtras
extras
freeNamesDeclExtras :: IfaceDeclExtras -> NameSet
(IfaceIdExtras IfaceIdExtras
id_extras)
= IfaceIdExtras -> UniqSet Name
freeNamesIdExtras IfaceIdExtras
id_extras
freeNamesDeclExtras (IfaceDataExtras Maybe Fixity
_ [Name]
insts [AnnPayload]
_ [IfaceIdExtras]
subs)
= [UniqSet Name] -> UniqSet Name
unionNameSets ([Name] -> UniqSet Name
mkNameSet [Name]
insts forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map IfaceIdExtras -> UniqSet Name
freeNamesIdExtras [IfaceIdExtras]
subs)
freeNamesDeclExtras (IfaceClassExtras Maybe Fixity
_ [Name]
insts [AnnPayload]
_ [IfaceIdExtras]
subs [Name]
defms)
= [UniqSet Name] -> UniqSet Name
unionNameSets forall a b. (a -> b) -> a -> b
$
[Name] -> UniqSet Name
mkNameSet [Name]
insts forall a. a -> [a] -> [a]
: [Name] -> UniqSet Name
mkNameSet [Name]
defms forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map IfaceIdExtras -> UniqSet Name
freeNamesIdExtras [IfaceIdExtras]
subs
freeNamesDeclExtras (IfaceSynonymExtras Maybe Fixity
_ [AnnPayload]
_)
= UniqSet Name
emptyNameSet
freeNamesDeclExtras (IfaceFamilyExtras Maybe Fixity
_ [Name]
insts [AnnPayload]
_)
= [Name] -> UniqSet Name
mkNameSet [Name]
insts
freeNamesDeclExtras IfaceDeclExtras
IfaceOtherDeclExtras
= UniqSet Name
emptyNameSet
freeNamesIdExtras :: IfaceIdExtras -> NameSet
(IdExtras Maybe Fixity
_ [IfaceRule]
rules [AnnPayload]
_) = [UniqSet Name] -> UniqSet Name
unionNameSets (forall a b. (a -> b) -> [a] -> [b]
map IfaceRule -> UniqSet Name
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 [forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix, forall a. Outputable a => a -> SDoc
ppr [AnnPayload]
anns]
ppr (IfaceFamilyExtras Maybe Fixity
fix [Name]
finsts [AnnPayload]
anns) = [SDoc] -> SDoc
vcat [forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix, forall a. Outputable a => a -> SDoc
ppr [Name]
finsts, forall a. Outputable a => a -> SDoc
ppr [AnnPayload]
anns]
ppr (IfaceDataExtras Maybe Fixity
fix [Name]
insts [AnnPayload]
anns [IfaceIdExtras]
stuff) = [SDoc] -> SDoc
vcat [forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix, [Name] -> SDoc
ppr_insts [Name]
insts, 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 [forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix, [Name] -> SDoc
ppr_insts [Name]
insts, forall a. Outputable a => a -> SDoc
ppr [AnnPayload]
anns,
[IfaceIdExtras] -> SDoc
ppr_id_extras_s [IfaceIdExtras]
stuff, 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 (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) = forall a. Outputable a => a -> SDoc
ppr Maybe Fixity
fix SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [IfaceRule]
rules) SDoc -> SDoc -> SDoc
$$ [SDoc] -> SDoc
vcat (forall a b. (a -> b) -> [a] -> [b]
map forall a. Outputable a => a -> SDoc
ppr [AnnPayload]
anns)
instance Binary IfaceDeclExtras where
get :: BinHandle -> IO IfaceDeclExtras
get BinHandle
_bh = 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; 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; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Name]
insts; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [AnnPayload]
anns; 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
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Name]
insts
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [AnnPayload]
anns
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceIdExtras]
methods
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; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix; 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; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [Name]
finsts; 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 = 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 { forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Fixity
fix; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh [IfaceRule]
rules; 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)
(forall a b. (a -> b) -> [a] -> [b]
map IfaceFamInst -> Name
ifFamInstAxiom (forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceFamInst]
fi_env OccName
n) forall a. [a] -> [a] -> [a]
++
forall a b. (a -> b) -> [a] -> [b]
map IfaceClsInst -> Name
ifDFun (forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceClsInst]
inst_env OccName
n))
(OccName -> [AnnPayload]
ann_fn OccName
n)
(forall a b. (a -> b) -> [a] -> [b]
map (OccName -> IfaceIdExtras
id_extras forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall name. HasOccName name => name -> OccName
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 = (forall a b. (a -> b) -> [a] -> [b]
map IfaceClsInst -> Name
ifDFun forall a b. (a -> b) -> a -> b
$ (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap IfaceAT -> [IfaceClsInst]
at_extras [IfaceAT]
ats)
forall a. [a] -> [a] -> [a]
++ forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceClsInst]
inst_env OccName
n)
meths :: [IfaceIdExtras]
meths = [OccName -> IfaceIdExtras
id_extras (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 <- [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)
(forall a b. (a -> b) -> [a] -> [b]
map IfaceFamInst -> Name
ifFamInstAxiom (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 = 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) (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
_) = forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [IfaceClsInst]
inst_env (forall a. NamedThing a => a -> OccName
getOccName IfaceDecl
decl)
lookupOccEnvL :: OccEnv [v] -> OccName -> [v]
lookupOccEnvL :: forall v. OccEnv [v] -> OccName -> [v]
lookupOccEnvL OccEnv [v]
env OccName
k = forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv [v]
env OccName
k forall a. Maybe a -> a -> a
`orElse` []
mkOrphMap :: (decl -> IsOrphan)
-> [decl]
-> (OccEnv [decl],
[decl])
mkOrphMap :: forall decl.
(decl -> IsOrphan) -> [decl] -> (OccEnv [decl], [decl])
mkOrphMap decl -> IsOrphan
get_key [decl]
decls
= forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (OccEnv [decl], [decl]) -> decl -> (OccEnv [decl], [decl])
go (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
= (forall a b.
(a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b
extendOccEnv_Acc (:) forall a. a -> [a]
Utils.singleton OccEnv [decl]
non_orphs OccName
occ decl
d, [decl]
orphs)
| Bool
otherwise = (OccEnv [decl]
non_orphs, decl
dforall a. a -> [a] -> [a]
:[decl]
orphs)
mkHashFun
:: HscEnv
-> ExternalPackageState
-> (Name -> IO Fingerprint)
mkHashFun :: HscEnv -> ExternalPackageState -> Name -> IO Fingerprint
mkHashFun HscEnv
hsc_env ExternalPackageState
eps Name
name
| forall u. GenModule (GenUnit u) -> Bool
isHoleModule Module
orig_mod
= Module -> IO Fingerprint
lookup (HomeUnit -> ModuleName -> Module
mkHomeModule HomeUnit
home_unit (forall unit. GenModule unit -> ModuleName
moduleName Module
orig_mod))
| Bool
otherwise
= Module -> IO Fingerprint
lookup Module
orig_mod
where
home_unit :: HomeUnit
home_unit = HscEnv -> HomeUnit
hsc_home_unit 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
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 -> forall (m :: * -> *) a. Monad m => a -> m a
return ModIface
iface
Maybe ModIface
Nothing ->
forall a. HscEnv -> IfG a -> IO a
initIfaceLoad HscEnv
hsc_env forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall gbl lcl a.
TcRnIf gbl lcl (MaybeErr SDoc a) -> TcRnIf gbl lcl a
withException
forall a b. (a -> b) -> a -> b
$ forall gbl lcl a. TcRnIf gbl lcl a -> TcRnIf gbl lcl a
withoutDynamicNow
forall a b. (a -> b) -> a -> b
$ forall lcl.
SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr SDoc ModIface)
loadInterface (String -> SDoc
text String
"lookupVers2") Module
mod WhereFrom
ImportBySystem
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a, b) -> b
snd (ModIfaceBackend -> OccName -> Maybe (OccName, Fingerprint)
mi_hash_fn (forall (phase :: ModIfacePhase).
ModIface_ phase -> IfaceBackendExts phase
mi_final_exts ModIface
iface) OccName
occ forall a. Maybe a -> a -> a
`orElse`
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"lookupVers1" (forall a. Outputable a => a -> SDoc
ppr Module
mod SDoc -> SDoc -> SDoc
<+> forall a. Outputable a => a -> SDoc
ppr OccName
occ))
mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload]
mkIfaceAnnCache :: [IfaceAnnotation] -> OccName -> [AnnPayload]
mkIfaceAnnCache [IfaceAnnotation]
anns
= \OccName
n -> forall a. OccEnv a -> OccName -> Maybe a
lookupOccEnv OccEnv [AnnPayload]
env OccName
n 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 = forall a. (a -> a -> a) -> [(OccName, a)] -> OccEnv a
mkOccEnv_C (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. [a] -> [a] -> [a]
(++)) (forall a b. (a -> b) -> [a] -> [b]
map IfaceAnnotation -> (OccName, [AnnPayload])
pair [IfaceAnnotation]
anns)