Skip to content
Snippets Groups Projects
Commit d83e1ac4 authored by Simon Marlow's avatar Simon Marlow
Browse files

Fix a bug to do with recursive modules in one-shot mode

The problem was that when loading interface files in checkOldIface, we
were not passing the If monad the mutable variable for use when
looking up entities in the *current* module, with the result that the
knots wouldn't be tied properly, and some instances of TyCons would
be incorrectly abstract.

This bug has subtle effects: for example, recompiling a module without
making any changes might lead to a slightly different result (noticed
due to the new interface-file fingerprints).  The bug doesn't lead to
any direct failures that we're aware of.
parent 0d80489c
Branches float
No related tags found
No related merge requests found
...@@ -136,6 +136,7 @@ newHscEnv dflags ...@@ -136,6 +136,7 @@ newHscEnv dflags
hsc_FC = fc_var, hsc_FC = fc_var,
hsc_MLC = mlc_var, hsc_MLC = mlc_var,
hsc_OptFuel = optFuel, hsc_OptFuel = optFuel,
hsc_type_env_var = Nothing,
hsc_global_rdr_env = emptyGlobalRdrEnv, hsc_global_rdr_env = emptyGlobalRdrEnv,
hsc_global_type_env = emptyNameEnv } ) } hsc_global_type_env = emptyNameEnv } ) }
...@@ -335,7 +336,19 @@ type Compiler result = HscEnv ...@@ -335,7 +336,19 @@ type Compiler result = HscEnv
-- Compile Haskell, boot and extCore in OneShot mode. -- Compile Haskell, boot and extCore in OneShot mode.
hscCompileOneShot :: Compiler HscStatus hscCompileOneShot :: Compiler HscStatus
hscCompileOneShot hscCompileOneShot hsc_env mod_summary src_changed mb_old_iface mb_i_of_n
= do
-- One-shot mode needs a knot-tying mutable variable for interface files.
-- See TcRnTypes.TcGblEnv.tcg_type_env_var.
type_env_var <- newIORef emptyNameEnv
let
mod = ms_mod mod_summary
hsc_env' = hsc_env{ hsc_type_env_var = Just (mod, type_env_var) }
---
hscCompilerOneShot' hsc_env' mod_summary src_changed mb_old_iface mb_i_of_n
hscCompilerOneShot' :: Compiler HscStatus
hscCompilerOneShot'
= hscCompiler norecompOneShot oneShotMsg (genComp backend boot_backend) = hscCompiler norecompOneShot oneShotMsg (genComp backend boot_backend)
where where
backend inp = hscSimplify inp >>= hscNormalIface >>= hscWriteIface >>= hscOneShot backend inp = hscSimplify inp >>= hscNormalIface >>= hscWriteIface >>= hscOneShot
......
...@@ -206,6 +206,10 @@ data HscEnv ...@@ -206,6 +206,10 @@ data HscEnv
-- by limiting the number of transformations, -- by limiting the number of transformations,
-- we can use binary search to help find compiler bugs. -- we can use binary search to help find compiler bugs.
hsc_type_env_var :: Maybe (Module, IORef TypeEnv),
-- Used for one-shot compilation only, to initialise
-- the IfGblEnv. See TcRnTypes.TcGblEnv.tcg_type_env_var
hsc_global_rdr_env :: GlobalRdrEnv, hsc_global_rdr_env :: GlobalRdrEnv,
hsc_global_type_env :: TypeEnv hsc_global_type_env :: TypeEnv
} }
......
...@@ -69,11 +69,13 @@ initTc :: HscEnv ...@@ -69,11 +69,13 @@ initTc :: HscEnv
initTc hsc_env hsc_src keep_rn_syntax mod do_this initTc hsc_env hsc_src keep_rn_syntax mod do_this
= do { errs_var <- newIORef (emptyBag, emptyBag) ; = do { errs_var <- newIORef (emptyBag, emptyBag) ;
tvs_var <- newIORef emptyVarSet ; tvs_var <- newIORef emptyVarSet ;
type_env_var <- newIORef emptyNameEnv ;
dfuns_var <- newIORef emptyNameSet ; dfuns_var <- newIORef emptyNameSet ;
keep_var <- newIORef emptyNameSet ; keep_var <- newIORef emptyNameSet ;
th_var <- newIORef False ; th_var <- newIORef False ;
dfun_n_var <- newIORef 1 ; dfun_n_var <- newIORef 1 ;
type_env_var <- case hsc_type_env_var hsc_env of {
Just (_mod, te_var) -> return te_var ;
Nothing -> newIORef emptyNameEnv } ;
let { let {
maybe_rn_syntax empty_val maybe_rn_syntax empty_val
| keep_rn_syntax = Just empty_val | keep_rn_syntax = Just empty_val
...@@ -951,9 +953,11 @@ initIfaceCheck :: HscEnv -> IfG a -> IO a ...@@ -951,9 +953,11 @@ initIfaceCheck :: HscEnv -> IfG a -> IO a
-- Used when checking the up-to-date-ness of the old Iface -- Used when checking the up-to-date-ness of the old Iface
-- Initialise the environment with no useful info at all -- Initialise the environment with no useful info at all
initIfaceCheck hsc_env do_this initIfaceCheck hsc_env do_this
= do { let gbl_env = IfGblEnv { if_rec_types = Nothing } = do let rec_types = case hsc_type_env_var hsc_env of
; initTcRnIf 'i' hsc_env gbl_env () do_this Just (mod,var) -> Just (mod, readMutVar var)
} Nothing -> Nothing
gbl_env = IfGblEnv { if_rec_types = rec_types }
initTcRnIf 'i' hsc_env gbl_env () do_this
initIfaceTc :: ModIface initIfaceTc :: ModIface
-> (TcRef TypeEnv -> IfL a) -> TcRnIf gbl lcl a -> (TcRef TypeEnv -> IfL a) -> TcRnIf gbl lcl a
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment