summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/GHC/Driver/Backpack.hs7
-rw-r--r--compiler/GHC/Driver/Make.hs60
-rw-r--r--compiler/GHC/StgToCmm/Expr.hs-boot7
-rw-r--r--compiler/GHC/Unit/Module/Graph.hs8
-rw-r--r--testsuite/tests/backpack/should_compile/bkp58.stderr4
-rw-r--r--testsuite/tests/backpack/should_compile/bkp60.stderr4
-rw-r--r--testsuite/tests/deriving/should_fail/T14365.stderr1
-rw-r--r--testsuite/tests/deriving/should_fail/T21087b.stderr5
-rw-r--r--testsuite/tests/driver/T14075/T14075.stdout9
-rw-r--r--testsuite/tests/driver/T20030/test1/T20030_test1.stderr4
-rw-r--r--testsuite/tests/driver/T20030/test1/T20030_test1j.stderr4
-rw-r--r--testsuite/tests/driver/T20030/test3/T20030_test3.stderr15
-rw-r--r--testsuite/tests/driver/T20300/T20300.stderr4
-rw-r--r--testsuite/tests/driver/recomp-boot-dyn-too/recomp-boot-dyn-too.stdout6
-rw-r--r--testsuite/tests/driver/recomp-boot/recomp-boot.stdout10
-rw-r--r--testsuite/tests/driver/recomp-boot2/recomp-boot2.stdout14
-rw-r--r--testsuite/tests/ghci/T11827/all.T2
-rw-r--r--testsuite/tests/ghci/scripts/T20217.stdout4
18 files changed, 78 insertions, 90 deletions
diff --git a/compiler/GHC/Driver/Backpack.hs b/compiler/GHC/Driver/Backpack.hs
index b4e530a3e9..a0a66b251f 100644
--- a/compiler/GHC/Driver/Backpack.hs
+++ b/compiler/GHC/Driver/Backpack.hs
@@ -920,7 +920,12 @@ hsModuleToModSummary home_keys pn hsc_src modname
-- Now, what are the dependencies.
let inst_nodes = map NodeKey_Unit inst_deps
- mod_nodes = [k | (_, mnwib) <- msDeps ms, let k = NodeKey_Module (ModNodeKeyWithUid (fmap unLoc mnwib) (moduleUnitId this_mod)), k `elem` home_keys]
+ mod_nodes =
+ -- hs-boot edge
+ [k | k <- [NodeKey_Module (ModNodeKeyWithUid (GWIB (ms_mod_name ms) IsBoot) (moduleUnitId this_mod))], NotBoot == isBootSummary ms, k `elem` home_keys ] ++
+ -- Normal edges
+ [k | (_, mnwib) <- msDeps ms, let k = NodeKey_Module (ModNodeKeyWithUid (fmap unLoc mnwib) (moduleUnitId this_mod)), k `elem` home_keys]
+
return (ModuleNode (mod_nodes ++ inst_nodes) ms)
diff --git a/compiler/GHC/Driver/Make.hs b/compiler/GHC/Driver/Make.hs
index 6023d3a914..df3f636732 100644
--- a/compiler/GHC/Driver/Make.hs
+++ b/compiler/GHC/Driver/Make.hs
@@ -680,8 +680,6 @@ load' cache how_much mHscMessage mod_graph = do
liftIO $ debugTraceMsg logger 2 (hang (text "Ready for upsweep")
2 (ppr build_plan))
- let direct_deps = mkDepsMap (mgModSummaries' mod_graph)
-
n_jobs <- case parMakeCount (hsc_dflags hsc_env) of
Nothing -> liftIO getNumProcessors
Just n -> return n
@@ -689,7 +687,7 @@ load' cache how_much mHscMessage mod_graph = do
setSession $ hscUpdateHUG (unitEnv_map pruneHomeUnitEnv) hsc_env
hsc_env <- getSession
(upsweep_ok, hsc_env1, new_cache) <- withDeferredDiagnostics $
- liftIO $ upsweep n_jobs hsc_env mHscMessage (toCache pruned_cache) direct_deps build_plan
+ liftIO $ upsweep n_jobs hsc_env mHscMessage (toCache pruned_cache) build_plan
setSession hsc_env1
fmap (, new_cache) $ case upsweep_ok of
Failed -> loadFinish upsweep_ok
@@ -994,12 +992,11 @@ type RunMakeM a = ReaderT MakeEnv (MaybeT IO) a
-- See Note [Upsweep] for a high-level description.
interpretBuildPlan :: HomeUnitGraph
-> M.Map ModNodeKeyWithUid HomeModInfo
- -> (NodeKey -> [NodeKey])
-> [BuildPlan]
-> IO ( Maybe [ModuleGraphNode] -- Is there an unresolved cycle
, [MakeAction] -- Actions we need to run in order to build everything
, IO [Maybe (Maybe HomeModInfo)]) -- An action to query to get all the built modules at the end.
-interpretBuildPlan hug old_hpt deps_map plan = do
+interpretBuildPlan hug old_hpt plan = do
hug_var <- newMVar hug
((mcycle, plans), build_map) <- runStateT (buildLoop plan) (BuildLoopState M.empty 1 hug_var)
return (mcycle, plans, collect_results (buildDep build_map))
@@ -1041,7 +1038,7 @@ interpretBuildPlan hug old_hpt deps_map plan = do
home_mod_map <- getBuildMap
hug_var <- gets hug_var
-- 1. Get the transitive dependencies of this module, by looking up in the dependency map
- let direct_deps = deps_map (mkNodeKey mod)
+ let direct_deps = nodeDependencies False mod
doc_build_deps = map (expectJust "dep_map" . flip M.lookup home_mod_map) direct_deps
build_deps = map snd doc_build_deps
-- 2. Set the default way to build this node, not in a loop here
@@ -1049,11 +1046,10 @@ interpretBuildPlan hug old_hpt deps_map plan = do
case mod of
InstantiationNode uid iu ->
const Nothing <$> executeInstantiationNode mod_idx n_mods (wait_deps_hug hug_var build_deps) uid iu
- ModuleNode build_deps ms -> do
+ ModuleNode _build_deps ms -> do
let !old_hmi = M.lookup (msKey ms) old_hpt
rehydrate_mods = mapMaybe moduleGraphNodeModule <$> rehydrate_nodes
- build_deps_vars = map snd $ map (expectJust "build_deps" . flip M.lookup home_mod_map) build_deps
- hmi <- executeCompileNode mod_idx n_mods old_hmi (wait_deps_hug hug_var build_deps_vars) rehydrate_mods ms
+ hmi <- executeCompileNode mod_idx n_mods old_hmi (wait_deps_hug hug_var build_deps) rehydrate_mods ms
-- This global MVar is incrementally modified in order to avoid having to
-- recreate the HPT before compiling each module which leads to a quadratic amount of work.
hsc_env <- asks hsc_env
@@ -1063,9 +1059,8 @@ interpretBuildPlan hug old_hpt deps_map plan = do
maybeRehydrateAfter hmi new_hsc rehydrate_mods
)
return (Just hmi')
- LinkNode nks uid -> do
- let link_deps = map snd $ map (\nk -> expectJust "build_deps_link" . flip M.lookup home_mod_map $ nk) nks
- executeLinkNode (wait_deps_hug hug_var link_deps) (mod_idx, n_mods) uid nks
+ LinkNode _nks uid -> do
+ executeLinkNode (wait_deps_hug hug_var build_deps) (mod_idx, n_mods) uid direct_deps
return Nothing
@@ -1105,11 +1100,10 @@ upsweep
-> HscEnv -- ^ The base HscEnv, which is augmented for each module
-> Maybe Messager
-> M.Map ModNodeKeyWithUid HomeModInfo
- -> (NodeKey -> [NodeKey]) -- A function which computes the direct dependencies of a NodeKey
-> [BuildPlan]
-> IO (SuccessFlag, HscEnv, [HomeModInfo])
-upsweep n_jobs hsc_env mHscMessage old_hpt direct_deps build_plan = do
- (cycle, pipelines, collect_result) <- interpretBuildPlan (hsc_HUG hsc_env) old_hpt direct_deps build_plan
+upsweep n_jobs hsc_env mHscMessage old_hpt build_plan = do
+ (cycle, pipelines, collect_result) <- interpretBuildPlan (hsc_HUG hsc_env) old_hpt build_plan
runPipelines n_jobs hsc_env mHscMessage pipelines
res <- collect_result
@@ -1364,14 +1358,6 @@ modNodeMapSingleton k v = ModNodeMap (M.singleton k v)
modNodeMapUnionWith :: (a -> a -> a) -> ModNodeMap a -> ModNodeMap a -> ModNodeMap a
modNodeMapUnionWith f (ModNodeMap m) (ModNodeMap n) = ModNodeMap (M.unionWith f m n)
--- | Efficiently construct a map from a NodeKey to its list of transitive dependencies
-mkDepsMap :: [ModuleGraphNode] -> (NodeKey -> [NodeKey])
-mkDepsMap nodes =
- -- Important that we force this before returning a lambda so we can share the module graph
- -- for each node
- let !(mg, lookup_node) = moduleGraphNodes False nodes
- in \nk -> map (mkNodeKey . node_payload) $ outgoingG mg (expectJust "mkDepsMap" (lookup_node nk))
-
-- | If there are {-# SOURCE #-} imports between strongly connected
-- components in the topological sort, then those imports can
-- definitely be replaced by ordinary non-SOURCE imports: if SOURCE
@@ -1459,7 +1445,12 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
in map Right instantiation_nodes
++ maybeToList (linkNodes (instantiation_nodes ++ summaries) uid hue)
- calcDeps ms = [(ms_unitid ms, b, c) | (b, c) <- msDeps ms ]
+ calcDeps ms =
+ -- Add a dependency on the HsBoot file if it exists
+ -- This gets passed to the loopImports function which just ignores it if it
+ -- can't be found.
+ [(ms_unitid ms, NoPkgQual, GWIB (noLoc $ ms_mod_name ms) IsBoot) | NotBoot <- [isBootSummary ms] ] ++
+ [(ms_unitid ms, b, c) | (b, c) <- msDeps ms ]
dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
@@ -1878,7 +1869,7 @@ summariseModule
-> IO SummariseResult
-summariseModule hsc_env' home_unit old_summary_map is_boot (L loc wanted_mod) mb_pkg
+summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_pkg
maybe_buf excl_mods
| wanted_mod `elem` excl_mods
= return NotThere
@@ -1895,12 +1886,9 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L loc wanted_mod) mb
found <- findImportedModule hsc_env wanted_mod mb_pkg
case found of
Found location mod
- | isJust (ml_hs_file location) -> do
+ | isJust (ml_hs_file location) ->
-- Home package
- fresult <- just_found location mod
- return $ case fresult of
- Left err -> FoundHomeWithError (moduleUnitId mod, err)
- Right ms -> FoundHome ms
+ just_found location mod
| VirtUnit iud <- moduleUnit mod
, not (isHomeModule home_unit mod)
-> return $ FoundInstantiation iud
@@ -1922,8 +1910,14 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L loc wanted_mod) mb
-- It might have been deleted since the Finder last found it
maybe_h <- fileHashIfExists src_fn
case maybe_h of
- Nothing -> return $ Left $ noHsFileErr loc src_fn
- Just h -> new_summary_cache_check location' mod src_fn h
+ -- This situation can also happen if we have found the .hs file but the
+ -- .hs-boot file doesn't exist.
+ Nothing -> return NotThere
+ Just h -> do
+ fresult <- new_summary_cache_check location' mod src_fn h
+ return $ case fresult of
+ Left err -> FoundHomeWithError (moduleUnitId mod, err)
+ Right ms -> FoundHome ms
new_summary_cache_check loc mod src_fn h
| Just old_summary <- Map.lookup src_fn old_summary_map =
@@ -2111,9 +2105,11 @@ noModError hsc_env loc wanted_mod err
= mkPlainErrorMsgEnvelope loc $ GhcDriverMessage $ DriverUnknownMessage $ mkPlainError noHints $
cannotFindModule hsc_env wanted_mod err
+{-
noHsFileErr :: SrcSpan -> String -> DriverMessages
noHsFileErr loc path
= singleMessage $ mkPlainErrorMsgEnvelope loc (DriverFileNotFound path)
+ -}
moduleNotFoundErr :: ModuleName -> DriverMessages
moduleNotFoundErr mod = singleMessage $ mkPlainErrorMsgEnvelope noSrcSpan (DriverModuleNotFound mod)
diff --git a/compiler/GHC/StgToCmm/Expr.hs-boot b/compiler/GHC/StgToCmm/Expr.hs-boot
deleted file mode 100644
index 5dd63a81dc..0000000000
--- a/compiler/GHC/StgToCmm/Expr.hs-boot
+++ /dev/null
@@ -1,7 +0,0 @@
-module GHC.StgToCmm.Expr where
-
-import GHC.Cmm.Expr
-import GHC.StgToCmm.Monad
-import GHC.Types.Literal
-
-cgLit :: Literal -> FCode CmmExpr
diff --git a/compiler/GHC/Unit/Module/Graph.hs b/compiler/GHC/Unit/Module/Graph.hs
index 7ebc6c893b..08c9b727ca 100644
--- a/compiler/GHC/Unit/Module/Graph.hs
+++ b/compiler/GHC/Unit/Module/Graph.hs
@@ -53,7 +53,7 @@ import GHC.Driver.Backend
import GHC.Driver.Ppr
import GHC.Driver.Session
-import GHC.Types.SourceFile ( hscSourceString, HscSource (HsBootFile) )
+import GHC.Types.SourceFile ( hscSourceString )
import GHC.Unit.Module.ModSummary
import GHC.Unit.Module.Env
@@ -309,10 +309,8 @@ nodeDependencies drop_hs_boot_nodes = \case
LinkNode deps _uid -> deps
InstantiationNode uid iuid ->
NodeKey_Module . (\mod -> ModNodeKeyWithUid (GWIB mod NotBoot) uid) <$> uniqDSetToList (instUnitHoles iuid)
- ModuleNode deps ms ->
- [ NodeKey_Module $ (ModNodeKeyWithUid (GWIB (ms_mod_name ms) IsBoot) (ms_unitid ms))
- | not $ drop_hs_boot_nodes || ms_hsc_src ms == HsBootFile
- ] ++ map drop_hs_boot deps
+ ModuleNode deps _ms ->
+ map drop_hs_boot deps
where
-- Drop hs-boot nodes by using HsSrcFile as the key
hs_boot_key | drop_hs_boot_nodes = NotBoot -- is regular mod or signature
diff --git a/testsuite/tests/backpack/should_compile/bkp58.stderr b/testsuite/tests/backpack/should_compile/bkp58.stderr
index 3f36e43701..f7cffd24ba 100644
--- a/testsuite/tests/backpack/should_compile/bkp58.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp58.stderr
@@ -5,8 +5,8 @@
Instantiating consumer-impl
[1 of 1] Including common
[1 of 3] Compiling Impl[boot] ( consumer-impl/Impl.hs-boot, bkp58.out/consumer-impl/Impl.o-boot )
- [2 of 3] Compiling Downstream ( consumer-impl/Downstream.hs, bkp58.out/consumer-impl/Downstream.o )
- [3 of 3] Compiling Impl ( consumer-impl/Impl.hs, bkp58.out/consumer-impl/Impl.o )
+ [2 of 3] Compiling Impl ( consumer-impl/Impl.hs, bkp58.out/consumer-impl/Impl.o )
+ [3 of 3] Compiling Downstream ( consumer-impl/Downstream.hs, bkp58.out/consumer-impl/Downstream.o )
[3 of 3] Processing tie
Instantiating tie
[1 of 1] Including consumer-impl
diff --git a/testsuite/tests/backpack/should_compile/bkp60.stderr b/testsuite/tests/backpack/should_compile/bkp60.stderr
index 6a5732b961..4af21f67ed 100644
--- a/testsuite/tests/backpack/should_compile/bkp60.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp60.stderr
@@ -5,8 +5,8 @@
Instantiating consumer-impl
[1 of 1] Including common
[1 of 3] Compiling Impl[boot] ( consumer-impl/Impl.hs-boot, bkp60.out/consumer-impl/Impl.o-boot )
- [2 of 3] Compiling Downstream ( consumer-impl/Downstream.hs, bkp60.out/consumer-impl/Downstream.o )
- [3 of 3] Compiling Impl ( consumer-impl/Impl.hs, bkp60.out/consumer-impl/Impl.o )
+ [2 of 3] Compiling Impl ( consumer-impl/Impl.hs, bkp60.out/consumer-impl/Impl.o )
+ [3 of 3] Compiling Downstream ( consumer-impl/Downstream.hs, bkp60.out/consumer-impl/Downstream.o )
[3 of 3] Processing tie
Instantiating tie
[1 of 1] Including consumer-impl
diff --git a/testsuite/tests/deriving/should_fail/T14365.stderr b/testsuite/tests/deriving/should_fail/T14365.stderr
index a166953cf5..f8f106fea8 100644
--- a/testsuite/tests/deriving/should_fail/T14365.stderr
+++ b/testsuite/tests/deriving/should_fail/T14365.stderr
@@ -11,4 +11,3 @@ T14365B.hs-boot:7:1: error:
Cannot derive instances in hs-boot files
Write an instance declaration instead
• In the stand-alone deriving instance for ‘Foldable Foo’
-[3 of 3] Compiling T14365B ( T14365B.hs, T14365B.o )
diff --git a/testsuite/tests/deriving/should_fail/T21087b.stderr b/testsuite/tests/deriving/should_fail/T21087b.stderr
index 4caee4928e..6514e20ecf 100644
--- a/testsuite/tests/deriving/should_fail/T21087b.stderr
+++ b/testsuite/tests/deriving/should_fail/T21087b.stderr
@@ -3,8 +3,3 @@
T21087b_aux.hs-boot:11:25: error:
• Class ‘KnownNat’ does not support user-specified instances.
• In the stand-alone deriving instance for ‘KnownNat Z’
-[3 of 3] Compiling T21087b_aux ( T21087b_aux.hs, T21087b_aux.o )
-
-T21087b_aux.hs:11:25: error:
- • Class ‘KnownNat’ does not support user-specified instances.
- • In the stand-alone deriving instance for ‘KnownNat Z’
diff --git a/testsuite/tests/driver/T14075/T14075.stdout b/testsuite/tests/driver/T14075/T14075.stdout
index f5fac2d604..f84cd727f2 100644
--- a/testsuite/tests/driver/T14075/T14075.stdout
+++ b/testsuite/tests/driver/T14075/T14075.stdout
@@ -1,4 +1,5 @@
-[1 of 4] Compiling O ( O.hs, O.o )
-[2 of 4] Compiling F[boot] ( F.hs-boot, F.o-boot )
-[3 of 4] Compiling V ( V.hs, V.o )
-[4 of 4] Compiling F ( F.hs, F.o )
+[1 of 5] Compiling O ( O.hs, O.o )
+[2 of 5] Compiling F[boot] ( F.hs-boot, F.o-boot )
+[3 of 5] Compiling V[boot] ( V.hs-boot, V.o-boot )
+[4 of 5] Compiling V ( V.hs, V.o )
+[5 of 5] Compiling F ( F.hs, F.o )
diff --git a/testsuite/tests/driver/T20030/test1/T20030_test1.stderr b/testsuite/tests/driver/T20030/test1/T20030_test1.stderr
index 81b29def80..8ee2810d59 100644
--- a/testsuite/tests/driver/T20030/test1/T20030_test1.stderr
+++ b/testsuite/tests/driver/T20030/test1/T20030_test1.stderr
@@ -9,5 +9,5 @@
[ 9 of 13] Compiling E ( E.hs, E.o )
[10 of 13] Compiling I ( I.hs, I.o )
[11 of 13] Compiling J[boot] ( J.hs-boot, J.o-boot )
-[12 of 13] Compiling K ( K.hs, K.o )
-[13 of 13] Compiling J ( J.hs, J.o )
+[12 of 13] Compiling J ( J.hs, J.o )
+[13 of 13] Compiling K ( K.hs, K.o )
diff --git a/testsuite/tests/driver/T20030/test1/T20030_test1j.stderr b/testsuite/tests/driver/T20030/test1/T20030_test1j.stderr
index 81b29def80..8ee2810d59 100644
--- a/testsuite/tests/driver/T20030/test1/T20030_test1j.stderr
+++ b/testsuite/tests/driver/T20030/test1/T20030_test1j.stderr
@@ -9,5 +9,5 @@
[ 9 of 13] Compiling E ( E.hs, E.o )
[10 of 13] Compiling I ( I.hs, I.o )
[11 of 13] Compiling J[boot] ( J.hs-boot, J.o-boot )
-[12 of 13] Compiling K ( K.hs, K.o )
-[13 of 13] Compiling J ( J.hs, J.o )
+[12 of 13] Compiling J ( J.hs, J.o )
+[13 of 13] Compiling K ( K.hs, K.o )
diff --git a/testsuite/tests/driver/T20030/test3/T20030_test3.stderr b/testsuite/tests/driver/T20030/test3/T20030_test3.stderr
index 91c3869e70..ffa4f5a95d 100644
--- a/testsuite/tests/driver/T20030/test3/T20030_test3.stderr
+++ b/testsuite/tests/driver/T20030/test3/T20030_test3.stderr
@@ -1,7 +1,8 @@
-[1 of 7] Compiling L[boot] ( L.hs-boot, L.o-boot )
-[2 of 7] Compiling M[boot] ( M.hs-boot, M.o-boot )
-[3 of 7] Compiling O[boot] ( O.hs-boot, O.o-boot )
-[4 of 7] Compiling O ( O.hs, O.o )
-[5 of 7] Compiling L ( L.hs, L.o )
-[6 of 7] Compiling M ( M.hs, M.o )
-[7 of 7] Compiling N ( N.hs, N.o )
+[1 of 8] Compiling L[boot] ( L.hs-boot, L.o-boot )
+[2 of 8] Compiling M[boot] ( M.hs-boot, M.o-boot )
+[3 of 8] Compiling O[boot] ( O.hs-boot, O.o-boot )
+[4 of 8] Compiling O ( O.hs, O.o )
+[5 of 8] Compiling L ( L.hs, L.o )
+[6 of 8] Compiling M ( M.hs, M.o )
+[7 of 8] Compiling N[boot] ( N.hs-boot, N.o-boot )
+[8 of 8] Compiling N ( N.hs, N.o )
diff --git a/testsuite/tests/driver/T20300/T20300.stderr b/testsuite/tests/driver/T20300/T20300.stderr
index 37b55fd9c1..0698d9bf0e 100644
--- a/testsuite/tests/driver/T20300/T20300.stderr
+++ b/testsuite/tests/driver/T20300/T20300.stderr
@@ -1,4 +1,4 @@
[1 of 4] Compiling T[boot] ( T.hs-boot, nothing )
-[2 of 4] Compiling S ( S.hs, S.o, S.dyn_o )
-[3 of 4] Compiling T ( T.hs, nothing )
+[2 of 4] Compiling T ( T.hs, nothing )
+[3 of 4] Compiling S ( S.hs, S.o, S.dyn_o )
[4 of 4] Compiling Top ( Top.hs, nothing )
diff --git a/testsuite/tests/driver/recomp-boot-dyn-too/recomp-boot-dyn-too.stdout b/testsuite/tests/driver/recomp-boot-dyn-too/recomp-boot-dyn-too.stdout
index e8ce474459..fc1844104f 100644
--- a/testsuite/tests/driver/recomp-boot-dyn-too/recomp-boot-dyn-too.stdout
+++ b/testsuite/tests/driver/recomp-boot-dyn-too/recomp-boot-dyn-too.stdout
@@ -1,4 +1,4 @@
-[1 of 2] Compiling A ( A.hs, A.o, A.dyn_o )
-[2 of 2] Compiling B ( B.hs, B.o, B.dyn_o )
[1 of 3] Compiling A[boot] ( A.hs-boot, A.o-boot, A.dyn_o-boot )
-[2 of 3] Compiling B ( B.hs, B.o, B.dyn_o ) [Source file changed]
+[2 of 3] Compiling A ( A.hs, A.o, A.dyn_o )
+[3 of 3] Compiling B ( B.hs, B.o, B.dyn_o )
+[3 of 3] Compiling B ( B.hs, B.o, B.dyn_o ) [Source file changed]
diff --git a/testsuite/tests/driver/recomp-boot/recomp-boot.stdout b/testsuite/tests/driver/recomp-boot/recomp-boot.stdout
index 5aa4618bfc..b84488bec1 100644
--- a/testsuite/tests/driver/recomp-boot/recomp-boot.stdout
+++ b/testsuite/tests/driver/recomp-boot/recomp-boot.stdout
@@ -1,6 +1,6 @@
-[1 of 3] Compiling C ( C.hs, C.o )
-[2 of 3] Compiling B ( B.hs, B.o )
-[3 of 3] Compiling A ( A.hs, A.o )
[1 of 4] Compiling C[boot] ( C.hs-boot, C.o-boot )
-[2 of 4] Compiling B ( B.hs, B.o ) [Source file changed]
-[3 of 4] Compiling A ( A.hs, A.o ) [B changed]
+[2 of 4] Compiling C ( C.hs, C.o )
+[3 of 4] Compiling B ( B.hs, B.o )
+[4 of 4] Compiling A ( A.hs, A.o )
+[3 of 4] Compiling B ( B.hs, B.o ) [Source file changed]
+[4 of 4] Compiling A ( A.hs, A.o ) [B changed]
diff --git a/testsuite/tests/driver/recomp-boot2/recomp-boot2.stdout b/testsuite/tests/driver/recomp-boot2/recomp-boot2.stdout
index 0ad0041e30..6e795da149 100644
--- a/testsuite/tests/driver/recomp-boot2/recomp-boot2.stdout
+++ b/testsuite/tests/driver/recomp-boot2/recomp-boot2.stdout
@@ -1,10 +1,10 @@
-[1 of 5] Compiling C ( C.hs, C.o )
-[2 of 5] Compiling B ( B.hs, B.o )
-[3 of 5] Compiling A ( A.hs, A.o )
-[4 of 5] Compiling M ( M.hs, M.o )
-[5 of 5] Compiling Top ( Top.hs, Top.o )
[1 of 6] Compiling C[boot] ( C.hs-boot, C.o-boot )
-[2 of 6] Compiling B ( B.hs, B.o ) [Source file changed]
-[3 of 6] Compiling A ( A.hs, A.o ) [B changed]
+[2 of 6] Compiling C ( C.hs, C.o )
+[3 of 6] Compiling B ( B.hs, B.o )
+[4 of 6] Compiling A ( A.hs, A.o )
+[5 of 6] Compiling M ( M.hs, M.o )
+[6 of 6] Compiling Top ( Top.hs, Top.o )
+[3 of 6] Compiling B ( B.hs, B.o ) [Source file changed]
+[4 of 6] Compiling A ( A.hs, A.o ) [B changed]
[5 of 6] Compiling M ( M.hs, M.o ) [A changed]
[6 of 6] Compiling Top ( Top.hs, Top.o ) [M changed]
diff --git a/testsuite/tests/ghci/T11827/all.T b/testsuite/tests/ghci/T11827/all.T
index eee5b8849d..d29c6de795 100644
--- a/testsuite/tests/ghci/T11827/all.T
+++ b/testsuite/tests/ghci/T11827/all.T
@@ -1,2 +1,2 @@
test('T11827', [extra_files(['A.hs', 'A.hs-boot', 'B.hs']),
- expect_broken(11827)], ghci_script, ['T11827.script'])
+ ], ghci_script, ['T11827.script'])
diff --git a/testsuite/tests/ghci/scripts/T20217.stdout b/testsuite/tests/ghci/scripts/T20217.stdout
index fa229321bf..49a5244c5f 100644
--- a/testsuite/tests/ghci/scripts/T20217.stdout
+++ b/testsuite/tests/ghci/scripts/T20217.stdout
@@ -1,5 +1,5 @@
[1 of 3] Compiling T20217A[boot] ( T20217A.hs-boot, nothing )
-[2 of 3] Compiling T20217 ( T20217.hs, nothing )
-[3 of 3] Compiling T20217A ( T20217A.hs, nothing )
+[2 of 3] Compiling T20217A ( T20217A.hs, nothing )
+[3 of 3] Compiling T20217 ( T20217.hs, nothing )
Ok, three modules loaded.
Ok, three modules loaded.