summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn Ericson <John.Ericson@Obsidian.Systems>2020-04-30 11:09:24 -0400
committerCale Gibbard <cgibbard@gmail.com>2020-12-28 12:28:35 -0500
commit2113a1d600e579bb0f54a0526a03626f105c0365 (patch)
tree746a62bb019f399f3921fdfb1f1f15ae521f6c90
parentcbc7c3dda6bdf4acb760ca9eb545faeb98ab0dbe (diff)
downloadhaskell-2113a1d600e579bb0f54a0526a03626f105c0365.tar.gz
Put hole instantiation typechecking in the module graph and fix driver batch mode backpack edges
Backpack instantiations need to be typechecked to make sure that the arguments fit the parameters. `tcRnInstantiateSignature` checks instantiations with concrete modules, while `tcRnCheckUnit` checks instantiations with free holes (signatures in the current modules). Before this change, it worked that `tcRnInstantiateSignature` was called after typechecking the argument module, see `HscMain.hsc_typecheck`, while `tcRnCheckUnit` was called in `unsweep'` where-bound in `GhcMake.upsweep`. `tcRnCheckUnit` was called once per each instantiation once all the argument sigs were processed. This was done with simple "to do" and "already done" accumulators in the fold. `parUpsweep` did not implement the change. With this change, `tcRnCheckUnit` instead is associated with its own node in the `ModuleGraph`. Nodes are now: ```haskell data ModuleGraphNode -- | Instantiation nodes track the instantiation of other units -- (backpack dependencies) with the holes (signatures) of the current package. = InstantiationNode InstantiatedUnit -- | There is a module summary node for each module, signature, and boot module being built. | ModuleNode ExtendedModSummary ``` instead of just `ModSummary`; the `InstantiationNode` case is the instantiation of a unit to be checked. The dependencies of such nodes are the same "free holes" as was checked with the accumulator before. Both versions of upsweep on such a node call `tcRnCheckUnit`. There previously was an `implicitRequirements` function which would crawl through every non-current-unit module dep to look for all free holes (signatures) to add as dependencies in `GHC.Driver.Make`. But this is no good: we shouldn't be looking for transitive anything when building the graph: the graph should only have immediate edges and the scheduler takes care that all transitive requirements are met. So `GHC.Driver.Make` stopped using `implicitRequirements`, and instead uses a new `implicitRequirementsShallow`, which just returns the outermost instantiation node (or module name if the immediate dependency is itself a signature). The signature dependencies are just treated like any other imported module, but the module ones then go in a list stored in the `ModuleNode` next to the `ModSummary` as the "extra backpack dependencies". When `downsweep` creates the mod summaries, it adds this information too. ------ There is one code quality, and possible correctness thing left: In addition to `implicitRequirements` there is `findExtraSigImports`, which says something like "if you are an instantiation argument (you are substituted or a signature), you need to import its things too". This is a little non-local so I am not quite sure how to get rid of it in `GHC.Driver.Make`, but we probably should eventually. First though, let's try to make a test case that observes that we don't do this, lest it actually be unneeded. Until then, I'm happy to leave it as is. ------ Beside the ability to use `-j`, the other major user-visibile side effect of this change is that that the --make progress log now includes "Instantiating" messages for these new nodes. Those also are numbered like module nodes and count towards the total. ------ Fixes #17188 Updates hackage submomdule Metric Increase: T12425 T13035
-rw-r--r--compiler/GHC/Data/Graph/Directed.hs5
-rw-r--r--compiler/GHC/Driver/Backpack.hs59
-rw-r--r--compiler/GHC/Driver/Main.hs31
-rw-r--r--compiler/GHC/Driver/Make.hs684
-rw-r--r--compiler/GHC/Driver/MakeFile.hs23
-rw-r--r--compiler/GHC/Runtime/Eval.hs4
-rw-r--r--compiler/GHC/Tc/Utils/Backpack.hs55
-rw-r--r--compiler/GHC/Unit/Module/Graph.hs133
-rw-r--r--compiler/GHC/Unit/Module/ModSummary.hs57
-rw-r--r--compiler/GHC/Unit/State.hs14
-rw-r--r--compiler/GHC/Unit/Types.hs4
-rw-r--r--ghc/GHCi/UI.hs11
-rw-r--r--testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout1
-rw-r--r--testsuite/tests/backpack/reexport/bkpreex01.stderr7
-rw-r--r--testsuite/tests/backpack/reexport/bkpreex02.stderr15
-rw-r--r--testsuite/tests/backpack/reexport/bkpreex06.stderr6
-rw-r--r--testsuite/tests/backpack/reexport/bkpreex08.stderr5
-rw-r--r--testsuite/tests/backpack/reexport/bkpreex09.stderr5
-rw-r--r--testsuite/tests/backpack/reexport/bkpreex10.stderr5
-rw-r--r--testsuite/tests/backpack/should_compile/T13140.stderr7
-rw-r--r--testsuite/tests/backpack/should_compile/T13214.stderr17
-rw-r--r--testsuite/tests/backpack/should_compile/T13250.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/T13323.stderr3
-rw-r--r--testsuite/tests/backpack/should_compile/bkp01.stderr7
-rw-r--r--testsuite/tests/backpack/should_compile/bkp02.stderr3
-rw-r--r--testsuite/tests/backpack/should_compile/bkp07.stderr5
-rw-r--r--testsuite/tests/backpack/should_compile/bkp08.stderr3
-rw-r--r--testsuite/tests/backpack/should_compile/bkp09.stderr13
-rw-r--r--testsuite/tests/backpack/should_compile/bkp10.stderr5
-rw-r--r--testsuite/tests/backpack/should_compile/bkp11.stderr5
-rw-r--r--testsuite/tests/backpack/should_compile/bkp12.stderr11
-rw-r--r--testsuite/tests/backpack/should_compile/bkp14.stderr5
-rw-r--r--testsuite/tests/backpack/should_compile/bkp15.stderr13
-rw-r--r--testsuite/tests/backpack/should_compile/bkp16.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp17.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp18.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp19.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp20.stderr13
-rw-r--r--testsuite/tests/backpack/should_compile/bkp21.stderr12
-rw-r--r--testsuite/tests/backpack/should_compile/bkp23.stderr35
-rw-r--r--testsuite/tests/backpack/should_compile/bkp24.stderr13
-rw-r--r--testsuite/tests/backpack/should_compile/bkp25.stderr7
-rw-r--r--testsuite/tests/backpack/should_compile/bkp26.stderr3
-rw-r--r--testsuite/tests/backpack/should_compile/bkp27.stderr3
-rw-r--r--testsuite/tests/backpack/should_compile/bkp28.stderr5
-rw-r--r--testsuite/tests/backpack/should_compile/bkp29.stderr6
-rw-r--r--testsuite/tests/backpack/should_compile/bkp30.stderr6
-rw-r--r--testsuite/tests/backpack/should_compile/bkp31.stderr9
-rw-r--r--testsuite/tests/backpack/should_compile/bkp32.stderr60
-rw-r--r--testsuite/tests/backpack/should_compile/bkp33.stderr3
-rw-r--r--testsuite/tests/backpack/should_compile/bkp34.stderr6
-rw-r--r--testsuite/tests/backpack/should_compile/bkp35.stderr6
-rw-r--r--testsuite/tests/backpack/should_compile/bkp36.stderr5
-rw-r--r--testsuite/tests/backpack/should_compile/bkp37.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp38.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp39.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp40.stderr2
-rw-r--r--testsuite/tests/backpack/should_compile/bkp41.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp42.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp43.stderr6
-rw-r--r--testsuite/tests/backpack/should_compile/bkp44.stderr8
-rw-r--r--testsuite/tests/backpack/should_compile/bkp45.stderr6
-rw-r--r--testsuite/tests/backpack/should_compile/bkp46.stderr1
-rw-r--r--testsuite/tests/backpack/should_compile/bkp47.stderr6
-rw-r--r--testsuite/tests/backpack/should_compile/bkp48.stderr11
-rw-r--r--testsuite/tests/backpack/should_compile/bkp49.stderr3
-rw-r--r--testsuite/tests/backpack/should_compile/bkp50.stderr3
-rw-r--r--testsuite/tests/backpack/should_compile/bkp51.stderr23
-rw-r--r--testsuite/tests/backpack/should_compile/bkp53.stderr6
-rw-r--r--testsuite/tests/backpack/should_compile/bkp54.stderr5
-rw-r--r--testsuite/tests/backpack/should_compile/bkp55.stderr5
-rw-r--r--testsuite/tests/backpack/should_compile/bkp57.stderr3
-rw-r--r--testsuite/tests/backpack/should_compile/bkp59.stderr3
-rw-r--r--testsuite/tests/backpack/should_fail/all.T4
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail04.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail05.stderr3
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail07.stderr4
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail09.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail12.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail13.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail14.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail15.stderr3
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail20.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail21.stderr6
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail28.stderr4
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail29.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail31.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail33.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail34.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail35.stderr3
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail36.stderr4
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail38.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail41.stderr3
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail42.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail47.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail48.stderr2
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail49.stderr4
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail50.bkp8
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail50.stderr16
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail51.bkp11
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail51.stderr8
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail52.bkp11
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail52.stderr16
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail53.bkp21
-rw-r--r--testsuite/tests/backpack/should_fail/bkpfail53.stderr17
-rw-r--r--testsuite/tests/ghc-api/downsweep/OldModLocation.hs3
-rw-r--r--testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs3
m---------utils/haddock0
108 files changed, 1145 insertions, 549 deletions
diff --git a/compiler/GHC/Data/Graph/Directed.hs b/compiler/GHC/Data/Graph/Directed.hs
index 806460d6df..e6adf612ea 100644
--- a/compiler/GHC/Data/Graph/Directed.hs
+++ b/compiler/GHC/Data/Graph/Directed.hs
@@ -1,7 +1,10 @@
-- (c) The University of Glasgow 2006
-{-# LANGUAGE CPP, ScopedTypeVariables, ViewPatterns #-}
+{-# LANGUAGE CPP #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE ViewPatterns #-}
module GHC.Data.Graph.Directed (
Graph, graphFromEdgedVerticesOrd, graphFromEdgedVerticesUniq,
diff --git a/compiler/GHC/Driver/Backpack.hs b/compiler/GHC/Driver/Backpack.hs
index b86ef6281b..3a3f94d4f0 100644
--- a/compiler/GHC/Driver/Backpack.hs
+++ b/compiler/GHC/Driver/Backpack.hs
@@ -60,7 +60,8 @@ import GHC.Unit.Env
import GHC.Unit.External
import GHC.Unit.State
import GHC.Unit.Finder
-import GHC.Unit.Module.ModSummary (showModMsg)
+import GHC.Unit.Module.Graph
+import GHC.Unit.Module.ModSummary
import GHC.Unit.Home.ModInfo
import GHC.Linker.Types
@@ -83,6 +84,7 @@ import Data.Version
import Data.IORef
import Data.Map (Map)
import qualified Data.Map as Map
+import qualified Data.Set as Set
-- | Entry point to compile a Backpack file.
doBackpack :: [FilePath] -> Ghc ()
@@ -534,19 +536,28 @@ backpackProgressMsg level dflags msg =
mkBackpackMsg :: BkpM Messager
mkBackpackMsg = do
level <- getBkpLevel
- return $ \hsc_env mod_index recomp mod_summary ->
+ return $ \hsc_env mod_index recomp node ->
let dflags = hsc_dflags hsc_env
state = hsc_units hsc_env
showMsg msg reason =
backpackProgressMsg level dflags $ pprWithUnitState state $
showModuleIndex mod_index <>
- msg <> showModMsg dflags (recompileRequired recomp) mod_summary
+ msg <> showModMsg dflags (recompileRequired recomp) node
<> reason
- in case recomp of
+ in case node of
+ InstantiationNode _ ->
+ case recomp of
+ MustCompile -> showMsg (text "Instantiating ") empty
+ UpToDate
+ | verbosity (hsc_dflags hsc_env) >= 2 -> showMsg (text "Skipping ") empty
+ | otherwise -> return ()
+ RecompBecause reason -> showMsg (text "Instantiating ") (text " [" <> text reason <> text "]")
+ ModuleNode _ ->
+ case recomp of
MustCompile -> showMsg (text "Compiling ") empty
UpToDate
- | verbosity (hsc_dflags hsc_env) >= 2 -> showMsg (text "Skipping ") empty
- | otherwise -> return ()
+ | verbosity (hsc_dflags hsc_env) >= 2 -> showMsg (text "Skipping ") empty
+ | otherwise -> return ()
RecompBecause reason -> showMsg (text "Compiling ") (text " [" <> text reason <> text "]")
-- | 'PprStyle' for Backpack messages; here we usually want the module to
@@ -679,6 +690,7 @@ convertHsModuleId (HsModuleId (L _ hsuid) (L _ modname)) = mkModule (convertHsCo
hsunitModuleGraph :: HsUnit HsComponentId -> BkpM ModuleGraph
hsunitModuleGraph unit = do
hsc_env <- getSession
+
let decls = hsunitBody unit
pn = hsPackageName (unLoc (hsunitName unit))
home_unit = hsc_home_unit hsc_env
@@ -693,16 +705,21 @@ hsunitModuleGraph unit = do
-- 2. For each hole which does not already have an hsig file,
-- create an "empty" hsig file to induce compilation for the
-- requirement.
- let node_map = Map.fromList [ ((ms_mod_name n, ms_hsc_src n == HsigFile), n)
- | n <- nodes ]
+ let hsig_set = Set.fromList
+ [ ms_mod_name ms
+ | ExtendedModSummary { emsModSummary = ms } <- nodes
+ , ms_hsc_src ms == HsigFile
+ ]
req_nodes <- fmap catMaybes . forM (homeUnitInstantiations home_unit) $ \(mod_name, _) ->
- let has_local = Map.member (mod_name, True) node_map
- in if has_local
+ if Set.member mod_name hsig_set
then return Nothing
- else fmap Just $ summariseRequirement pn mod_name
+ else fmap (Just . extendModSummaryNoDeps) $ summariseRequirement pn mod_name
+ -- Using extendModSummaryNoDeps here is okay because we're making a leaf node
+ -- representing a signature that can't depend on any other unit.
-- 3. Return the kaboodle
- return $ mkModuleGraph $ nodes ++ req_nodes
+ return $ mkModuleGraph' $
+ (ModuleNode <$> (nodes ++ req_nodes)) ++ instantiationNodes (hsc_units hsc_env)
summariseRequirement :: PackageName -> ModuleName -> BkpM ModSummary
summariseRequirement pn mod_name = do
@@ -755,14 +772,14 @@ summariseDecl :: PackageName
-> HscSource
-> Located ModuleName
-> Maybe (Located HsModule)
- -> BkpM ModSummary
+ -> BkpM ExtendedModSummary
summariseDecl pn hsc_src (L _ modname) (Just hsmod) = hsModuleToModSummary pn hsc_src modname hsmod
summariseDecl _pn hsc_src lmodname@(L loc modname) Nothing
= do hsc_env <- getSession
let dflags = hsc_dflags hsc_env
-- TODO: this looks for modules in the wrong place
r <- liftIO $ summariseModule hsc_env
- Map.empty -- GHC API recomp not supported
+ emptyModNodeMap -- GHC API recomp not supported
(hscSourceToIsBoot hsc_src)
lmodname
True -- Target lets you disallow, but not here
@@ -782,7 +799,7 @@ hsModuleToModSummary :: PackageName
-> HscSource
-> ModuleName
-> Located HsModule
- -> BkpM ModSummary
+ -> BkpM ExtendedModSummary
hsModuleToModSummary pn hsc_src modname
hsmod = do
let imps = hsmodImports (unLoc hsmod)
@@ -830,11 +847,13 @@ hsModuleToModSummary pn hsc_src modname
extra_sig_imports <- liftIO $ findExtraSigImports hsc_env hsc_src modname
let normal_imports = map convImport (implicit_imports ++ ordinary_imps)
- required_by_imports <- liftIO $ implicitRequirements hsc_env normal_imports
+ (implicit_sigs, inst_deps) <- liftIO $ implicitRequirementsShallow hsc_env normal_imports
-- So that Finder can find it, even though it doesn't exist...
this_mod <- liftIO $ addHomeModuleToFinder hsc_env modname location
- return ModSummary {
+ return $ ExtendedModSummary
+ { emsModSummary =
+ ModSummary {
ms_mod = this_mod,
ms_hsc_src = hsc_src,
ms_location = location,
@@ -849,7 +868,7 @@ hsModuleToModSummary pn hsc_src modname
-- due to merging, requirements may end up with
-- extra imports
++ extra_sig_imports
- ++ required_by_imports,
+ ++ ((,) Nothing . noLoc <$> implicit_sigs),
-- This is our hack to get the parse tree to the right spot
ms_parsed_mod = Just (HsParsedModule {
hpm_module = hsmod,
@@ -860,7 +879,9 @@ hsModuleToModSummary pn hsc_src modname
ms_obj_date = Nothing, -- TODO do this, but problem: hi_timestamp is BOGUS
ms_iface_date = hi_timestamp,
ms_hie_date = hie_timestamp
- }
+ }
+ , emsInstantiatedUnits = inst_deps
+ }
-- | Create a new, externally provided hashed unit id from
-- a hash.
diff --git a/compiler/GHC/Driver/Main.hs b/compiler/GHC/Driver/Main.hs
index 9560e32b50..22b0f1a07e 100644
--- a/compiler/GHC/Driver/Main.hs
+++ b/compiler/GHC/Driver/Main.hs
@@ -675,7 +675,7 @@ This is the only thing that isn't caught by the type-system.
-}
-type Messager = HscEnv -> (Int,Int) -> RecompileRequired -> ModSummary -> IO ()
+type Messager = HscEnv -> (Int,Int) -> RecompileRequired -> ModuleGraphNode -> IO ()
-- | This function runs GHC's frontend with recompilation
-- avoidance. Specifically, it checks if recompilation is needed,
@@ -698,8 +698,9 @@ hscIncrementalFrontend
hsc_env <- getHscEnv
let msg what = case mHscMessage of
- Just hscMessage -> hscMessage hsc_env mod_index what mod_summary
- Nothing -> return ()
+ -- We use extendModSummaryNoDeps because extra backpack deps are only needed for batch mode
+ Just hscMessage -> hscMessage hsc_env mod_index what (ModuleNode (extendModSummaryNoDeps mod_summary))
+ Nothing -> return ()
skip iface = do
liftIO $ msg UpToDate
@@ -1031,19 +1032,27 @@ oneShotMsg hsc_env recomp =
return ()
batchMsg :: Messager
-batchMsg hsc_env mod_index recomp mod_summary =
- case recomp of
- MustCompile -> showMsg (text "Compiling ") empty
- UpToDate
- | verbosity (hsc_dflags hsc_env) >= 2 -> showMsg (text "Skipping ") empty
- | otherwise -> return ()
- RecompBecause reason -> showMsg (text "Compiling ") (text " [" <> text reason <> text "]")
+batchMsg hsc_env mod_index recomp node = case node of
+ InstantiationNode _ ->
+ case recomp of
+ MustCompile -> showMsg (text "Instantiating ") empty
+ UpToDate
+ | verbosity (hsc_dflags hsc_env) >= 2 -> showMsg (text "Skipping ") empty
+ | otherwise -> return ()
+ RecompBecause reason -> showMsg (text "Instantiating ") (text " [" <> text reason <> text "]")
+ ModuleNode _ ->
+ case recomp of
+ MustCompile -> showMsg (text "Compiling ") empty
+ UpToDate
+ | verbosity (hsc_dflags hsc_env) >= 2 -> showMsg (text "Skipping ") empty
+ | otherwise -> return ()
+ RecompBecause reason -> showMsg (text "Compiling ") (text " [" <> text reason <> text "]")
where
dflags = hsc_dflags hsc_env
showMsg msg reason =
compilationProgressMsg dflags $
(showModuleIndex mod_index <>
- msg <> showModMsg dflags (recompileRequired recomp) mod_summary)
+ msg <> showModMsg dflags (recompileRequired recomp) node)
<> reason
--------------------------------------------------------------
diff --git a/compiler/GHC/Driver/Make.hs b/compiler/GHC/Driver/Make.hs
index 62eeb01e44..04354baf17 100644
--- a/compiler/GHC/Driver/Make.hs
+++ b/compiler/GHC/Driver/Make.hs
@@ -1,5 +1,11 @@
-{-# LANGUAGE BangPatterns, CPP, NondecreasingIndentation, ScopedTypeVariables #-}
-{-# LANGUAGE RecordWildCards, NamedFieldPuns #-}
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveTraversable #-}
+{-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE NondecreasingIndentation #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
@@ -14,6 +20,7 @@
module GHC.Driver.Make (
depanal, depanalE, depanalPartial,
load, load', LoadHowMuch(..),
+ instantiationNodes,
downsweep,
@@ -24,11 +31,13 @@ module GHC.Driver.Make (
summariseModule,
hscSourceToIsBoot,
findExtraSigImports,
- implicitRequirements,
+ implicitRequirementsShallow,
noModError, cyclicModuleErr,
moduleGraphNodes, SummaryNode,
- IsBootInterface(..)
+ IsBootInterface(..),
+
+ ModNodeMap(..), emptyModNodeMap, modNodeMapElems, modNodeMapLookup, modNodeMapInsert
) where
#include "HsVersions.h"
@@ -57,6 +66,7 @@ import GHC.Parser.Errors.Ppr
import GHC.Iface.Load ( cannotFindModule )
import GHC.IfaceToCore ( typecheckIface )
+import GHC.Iface.Recomp ( RecompileRequired ( MustCompile ) )
import GHC.Data.Bag ( unitBag, listToBag, unionManyBags, isEmptyBag )
import GHC.Data.Graph.Directed
@@ -208,13 +218,37 @@ depanalPartial excluded_mods allow_dup_roots = do
-- cached finder data.
liftIO $ flushFinderCaches hsc_env
- mod_summariesE <- liftIO $ downsweep hsc_env (mgModSummaries old_graph)
- excluded_mods allow_dup_roots
+ mod_summariesE <- liftIO $ downsweep
+ hsc_env (mgExtendedModSummaries old_graph)
+ excluded_mods allow_dup_roots
let
- (errs, mod_summaries) = partitionEithers mod_summariesE
- mod_graph = mkModuleGraph mod_summaries
+ (errs, mod_summaries) = partitionEithers mod_summariesE
+ mod_graph = mkModuleGraph' $
+ fmap ModuleNode mod_summaries ++ instantiationNodes (hsc_units hsc_env)
return (unionManyBags errs, mod_graph)
+-- | Collect the instantiations of dependencies to create 'InstantiationNode' work graph nodes.
+-- These are used to represent the type checking that is done after
+-- all the free holes (sigs in current package) relevant to that instantiation
+-- are compiled. This is necessary to catch some instantiation errors.
+--
+-- In the future, perhaps more of the work of instantiation could be moved here,
+-- instead of shoved in with the module compilation nodes. That could simplify
+-- backpack, and maybe hs-boot too.
+instantiationNodes :: UnitState -> [ModuleGraphNode]
+instantiationNodes unit_state = InstantiationNode <$> iuids_to_check
+ where
+ iuids_to_check :: [InstantiatedUnit]
+ iuids_to_check =
+ nubSort $ concatMap goUnitId (explicitUnits unit_state)
+ where
+ goUnitId uid =
+ [ recur
+ | VirtUnit indef <- [uid]
+ , inst <- instUnitInsts indef
+ , recur <- (indef :) $ goUnitId $ moduleUnit $ snd inst
+ ]
+
-- Note [Missing home modules]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- Sometimes user doesn't want GHC to pick up modules, not explicitly listed
@@ -431,7 +465,8 @@ load' how_much mHscMessage mod_graph = do
-- upsweep, and for removing from hpt all the modules
-- not in strict downwards closure, during calls to compile.
let mg2_with_srcimps :: [SCC ModSummary]
- mg2_with_srcimps = topSortModuleGraph True mod_graph Nothing
+ mg2_with_srcimps = filterToposortToModules $
+ topSortModuleGraph True mod_graph Nothing
-- If we can determine that any of the {-# SOURCE #-} imports
-- are definitely unnecessary, then emit a warning.
@@ -485,7 +520,8 @@ load' how_much mHscMessage mod_graph = do
-- This graph should be cycle-free.
-- If we're restricting the upsweep to a portion of the graph, we
-- also want to retain everything that is still stable.
- let full_mg :: [SCC ModSummary]
+ let full_mg, partial_mg0, partial_mg, unstable_mg :: [SCC ModuleGraphNode]
+ stable_mg :: [SCC ExtendedModSummary]
full_mg = topSortModuleGraph False mod_graph Nothing
maybe_top_mod = case how_much of
@@ -493,7 +529,6 @@ load' how_much mHscMessage mod_graph = do
LoadDependenciesOf m -> Just m
_ -> Nothing
- partial_mg0 :: [SCC ModSummary]
partial_mg0 = topSortModuleGraph False mod_graph maybe_top_mod
-- LoadDependenciesOf m: we want the upsweep to stop just
@@ -502,15 +537,16 @@ load' how_much mHscMessage mod_graph = do
partial_mg
| LoadDependenciesOf _mod <- how_much
= ASSERT( case last partial_mg0 of
- AcyclicSCC ms -> ms_mod_name ms == _mod; _ -> False )
+ AcyclicSCC (ModuleNode (ExtendedModSummary ms _)) -> ms_mod_name ms == _mod; _ -> False )
List.init partial_mg0
| otherwise
= partial_mg0
stable_mg =
- [ AcyclicSCC ms
- | AcyclicSCC ms <- full_mg,
- stable_mod_summary ms ]
+ [ AcyclicSCC ems
+ | AcyclicSCC (ModuleNode ems@(ExtendedModSummary ms _)) <- full_mg
+ , stable_mod_summary ms
+ ]
stable_mod_summary ms =
ms_mod_name ms `elementOfUniqSet` stable_obj ||
@@ -520,12 +556,13 @@ load' how_much mHscMessage mod_graph = do
-- NB. also keep cycles, we need to emit an error message later
unstable_mg = filter not_stable partial_mg
where not_stable (CyclicSCC _) = True
- not_stable (AcyclicSCC ms)
+ not_stable (AcyclicSCC (InstantiationNode _)) = True
+ not_stable (AcyclicSCC (ModuleNode (ExtendedModSummary ms _)))
= not $ stable_mod_summary ms
-- Load all the stable modules first, before attempting to load
-- an unstable module (#7231).
- mg = stable_mg ++ unstable_mg
+ mg = fmap (fmap ModuleNode) stable_mg ++ unstable_mg
-- clean up between compilations
let cleanup = cleanCurrentModuleTempFiles . hsc_dflags
@@ -546,7 +583,8 @@ load' how_much mHscMessage mod_graph = do
-- available; this should equal the domain of hpt3.
-- Get in in a roughly top .. bottom order (hence reverse).
- let modsDone = reverse modsUpswept
+ let nodesDone = reverse modsUpswept
+ (_, modsDone) = partitionNodes nodesDone
-- Try and do linking in some form, depending on whether the
-- upsweep was completely or only partially successful.
@@ -597,12 +635,13 @@ load' how_much mHscMessage mod_graph = do
do liftIO $ debugTraceMsg dflags 2 (text "Upsweep partially successful.")
let modsDone_names
- = map ms_mod modsDone
+ = map (ms_mod . emsModSummary) modsDone
let mods_to_zap_names
= findPartiallyCompletedCycles modsDone_names
mg2_with_srcimps
let (mods_to_clean, mods_to_keep) =
- partition ((`Set.member` mods_to_zap_names).ms_mod) modsDone
+ partition ((`Set.member` mods_to_zap_names).ms_mod) $
+ emsModSummary <$> modsDone
hsc_env1 <- getSession
let hpt4 = hsc_HPT hsc_env1
-- We must change the lifetime to TFL_CurrentModule for any temp
@@ -640,6 +679,14 @@ load' how_much mHscMessage mod_graph = do
modifySession $ \hsc_env -> hsc_env{ hsc_HPT = hpt5 }
loadFinish Failed linkresult
+partitionNodes
+ :: [ModuleGraphNode]
+ -> ( [InstantiatedUnit]
+ , [ExtendedModSummary]
+ )
+partitionNodes ns = partitionEithers $ flip fmap ns $ \case
+ InstantiationNode x -> Left x
+ ModuleNode x -> Right x
-- | Finish up after a load.
loadFinish :: GhcMonad m => SuccessFlag -> SuccessFlag -> m SuccessFlag
@@ -939,11 +986,11 @@ data LogQueue = LogQueue !(IORef [Maybe (WarnReason, Severity, SrcSpan, MsgDoc)]
-- | The graph of modules to compile and their corresponding result 'MVar' and
-- 'LogQueue'.
-type CompilationGraph = [(ModSummary, MVar SuccessFlag, LogQueue)]
+type CompilationGraph = [(ModuleGraphNode, MVar SuccessFlag, LogQueue)]
-- | Build a 'CompilationGraph' out of a list of strongly-connected modules,
-- also returning the first, if any, encountered module cycle.
-buildCompGraph :: [SCC ModSummary] -> IO (CompilationGraph, Maybe [ModSummary])
+buildCompGraph :: [SCC ModuleGraphNode] -> IO (CompilationGraph, Maybe [ModuleGraphNode])
buildCompGraph [] = return ([], Nothing)
buildCompGraph (scc:sccs) = case scc of
AcyclicSCC ms -> do
@@ -961,7 +1008,8 @@ buildCompGraph (scc:sccs) = case scc of
-- We need to treat boot modules specially when building compilation graphs,
-- since they break cycles. Regular source files and signature files are treated
-- equivalently.
-type BuildModule = ModuleWithIsBoot
+data BuildModule = BuildModule_Unit {-# UNPACK #-} !InstantiatedUnit | BuildModule_Module {-# UNPACK #-} !ModuleWithIsBoot
+ deriving (Eq, Ord)
-- | Tests if an 'HscSource' is a boot file, primarily for constructing elements
-- of 'BuildModule'. We conflate signatures and modules because they are bound
@@ -971,14 +1019,24 @@ hscSourceToIsBoot :: HscSource -> IsBootInterface
hscSourceToIsBoot HsBootFile = IsBoot
hscSourceToIsBoot _ = NotBoot
-mkBuildModule :: ModSummary -> BuildModule
-mkBuildModule ms = GWIB
+mkBuildModule :: ModuleGraphNode -> BuildModule
+mkBuildModule = \case
+ InstantiationNode x -> BuildModule_Unit x
+ ModuleNode ems -> BuildModule_Module $ mkBuildModule0 (emsModSummary ems)
+
+mkHomeBuildModule :: ModuleGraphNode -> NodeKey
+mkHomeBuildModule = \case
+ InstantiationNode x -> NodeKey_Unit x
+ ModuleNode ems -> NodeKey_Module $ mkHomeBuildModule0 (emsModSummary ems)
+
+mkBuildModule0 :: ModSummary -> ModuleWithIsBoot
+mkBuildModule0 ms = GWIB
{ gwib_mod = ms_mod ms
, gwib_isBoot = isBootSummary ms
}
-mkHomeBuildModule :: ModSummary -> ModuleNameWithIsBoot
-mkHomeBuildModule ms = GWIB
+mkHomeBuildModule0 :: ModSummary -> ModuleNameWithIsBoot
+mkHomeBuildModule0 ms = GWIB
{ gwib_mod = moduleName $ ms_mod ms
, gwib_isBoot = isBootSummary ms
}
@@ -994,16 +1052,13 @@ parUpsweep
-> HomePackageTable
-> StableModules
-> (HscEnv -> IO ())
- -> [SCC ModSummary]
+ -> [SCC ModuleGraphNode]
-> m (SuccessFlag,
- [ModSummary])
+ [ModuleGraphNode])
parUpsweep n_jobs mHscMessage old_hpt stable_mods cleanup sccs = do
hsc_env <- getSession
let dflags = hsc_dflags hsc_env
- when (not (null (instantiatedUnitsToCheck (hsc_units hsc_env)))) $
- throwGhcException (ProgramError "Backpack typechecking not supported with -j")
-
-- The bits of shared state we'll be using:
-- The global HscEnv is updated with the module's HMI when a module
@@ -1049,16 +1104,19 @@ parUpsweep n_jobs mHscMessage old_hpt stable_mods cleanup sccs = do
-- NB: For convenience, the last module of each loop (aka the module that
-- finishes the loop) is prepended to the beginning of the loop.
let graph = map fstOf3 (reverse comp_graph)
- boot_modules = mkModuleSet [ms_mod ms | ms <- graph, isBootSummary ms == IsBoot]
+ boot_modules = mkModuleSet
+ [ms_mod ms | ModuleNode (ExtendedModSummary ms _) <- graph, isBootSummary ms == IsBoot]
comp_graph_loops = go graph boot_modules
where
remove ms bm = case isBootSummary ms of
IsBoot -> delModuleSet bm (ms_mod ms)
NotBoot -> bm
go [] _ = []
- go mg@(ms:mss) boot_modules
+ go (InstantiationNode _ : mss) boot_modules
+ = go mss boot_modules
+ go mg@(mnode@(ModuleNode (ExtendedModSummary ms _)) : mss) boot_modules
| Just loop <- getModLoop ms mg (`elemModuleSet` boot_modules)
- = map mkBuildModule (ms:loop) : go mss (remove ms boot_modules)
+ = map mkBuildModule (mnode : loop) : go mss (remove ms boot_modules)
| otherwise
= go mss (remove ms boot_modules)
@@ -1075,12 +1133,20 @@ parUpsweep n_jobs mHscMessage old_hpt stable_mods cleanup sccs = do
-- compile this module.
let { spawnWorkers = forM comp_graph_w_idx $ \((mod,!mvar,!log_queue),!mod_idx) ->
forkIOWithUnmask $ \unmask -> do
- liftIO $ label_self $ unwords
- [ "worker --make thread"
- , "for module"
- , show (moduleNameString (ms_mod_name mod))
- , "number"
- , show mod_idx
+ liftIO $ label_self $ unwords $ concat
+ [ [ "worker --make thread" ]
+ , case mod of
+ InstantiationNode iuid ->
+ [ "for instantiation of unit"
+ , show $ VirtUnit iuid
+ ]
+ ModuleNode ems ->
+ [ "for module"
+ , show (moduleNameString (ms_mod_name (emsModSummary ems)))
+ ]
+ , ["number"
+ , show mod_idx
+ ]
]
-- Replace the default log_action with one that writes each
-- message to the module's log_queue. The main thread will
@@ -1098,11 +1164,17 @@ parUpsweep n_jobs mHscMessage old_hpt stable_mods cleanup sccs = do
-- Unmask asynchronous exceptions and perform the thread-local
-- work to compile the module (see parUpsweep_one).
m_res <- MC.try $ unmask $ prettyPrintGhcErrors lcl_dflags $
- parUpsweep_one mod home_mod_map comp_graph_loops
- lcl_dflags (hsc_home_unit hsc_env)
- mHscMessage cleanup
- par_sem hsc_env_var old_hpt_var
- stable_mods mod_idx (length sccs)
+ case mod of
+ InstantiationNode iuid -> do
+ hsc_env <- readMVar hsc_env_var
+ liftIO $ upsweep_inst hsc_env mHscMessage mod_idx (length sccs) iuid
+ pure Succeeded
+ ModuleNode ems ->
+ parUpsweep_one (emsModSummary ems) home_mod_map comp_graph_loops
+ lcl_dflags (hsc_home_unit hsc_env)
+ mHscMessage cleanup
+ par_sem hsc_env_var old_hpt_var
+ stable_mods mod_idx (length sccs)
res <- case m_res of
Right flag -> return flag
@@ -1225,7 +1297,7 @@ parUpsweep_one
parUpsweep_one mod home_mod_map comp_graph_loops lcl_dflags home_unit mHscMessage cleanup par_sem
hsc_env_var old_hpt_var stable_mods mod_index num_mods = do
- let this_build_mod = mkBuildModule mod
+ let this_build_mod = mkBuildModule0 mod
let home_imps = map unLoc $ ms_home_imps mod
let home_src_imps = map unLoc $ ms_home_srcimps mod
@@ -1234,7 +1306,7 @@ parUpsweep_one mod home_mod_map comp_graph_loops lcl_dflags home_unit mHscMessag
let textual_deps = Set.fromList $
zipWith f home_imps (repeat NotBoot) ++
zipWith f home_src_imps (repeat IsBoot)
- where f mn isBoot = GWIB
+ where f mn isBoot = BuildModule_Module $ GWIB
{ gwib_mod = mkHomeModule home_unit mn
, gwib_isBoot = isBoot
}
@@ -1268,29 +1340,36 @@ parUpsweep_one mod home_mod_map comp_graph_loops lcl_dflags home_unit mHscMessag
-- The loop that this module will finish. After this module successfully
-- compiles, this loop is going to get re-typechecked.
- let finish_loop = listToMaybe
- [ tail loop | loop <- comp_graph_loops
- , head loop == this_build_mod ]
+ let finish_loop :: Maybe [ModuleWithIsBoot]
+ finish_loop = listToMaybe
+ [ flip mapMaybe (tail loop) $ \case
+ BuildModule_Unit _ -> Nothing
+ BuildModule_Module ms -> Just ms
+ | loop <- comp_graph_loops
+ , head loop == BuildModule_Module this_build_mod
+ ]
-- If this module finishes a loop then it must depend on all the other
-- modules in that loop because the entire module loop is going to be
-- re-typechecked once this module gets compiled. These extra dependencies
-- are this module's "internal" loop dependencies, because this module is
-- inside the loop in question.
- let int_loop_deps = Set.fromList $
+ let int_loop_deps :: Set.Set BuildModule
+ int_loop_deps = Set.fromList $
case finish_loop of
Nothing -> []
- Just loop -> filter (/= this_build_mod) loop
+ Just loop -> BuildModule_Module <$> filter (/= this_build_mod) loop
-- If this module depends on a module within a loop then it must wait for
-- that loop to get re-typechecked, i.e. it must wait on the module that
-- finishes that loop. These extra dependencies are this module's
-- "external" loop dependencies, because this module is outside of the
-- loop(s) in question.
- let ext_loop_deps = Set.fromList
+ let ext_loop_deps :: Set.Set BuildModule
+ ext_loop_deps = Set.fromList
[ head loop | loop <- comp_graph_loops
, any (`Set.member` textual_deps) loop
- , this_build_mod `notElem` loop ]
+ , BuildModule_Module this_build_mod `notElem` loop ]
let all_deps = foldl1 Set.union [textual_deps, int_loop_deps, ext_loop_deps]
@@ -1298,7 +1377,8 @@ parUpsweep_one mod home_mod_map comp_graph_loops lcl_dflags home_unit mHscMessag
-- All of the module's home-module dependencies.
let home_deps_with_idx =
[ home_dep | dep <- Set.toList all_deps
- , Just home_dep <- [Map.lookup dep home_mod_map] ]
+ , Just home_dep <- [Map.lookup dep home_mod_map]
+ ]
-- Sort the list of dependencies in reverse-topological order. This way, by
-- the time we get woken up by the result of an earlier dependency,
@@ -1401,14 +1481,14 @@ parUpsweep_one mod home_mod_map comp_graph_loops lcl_dflags home_unit mHscMessag
-- There better had not be any cyclic groups here -- we check for them.
upsweep
:: forall m
- . GhcMonad m
+ . GhcMonad m
=> Maybe Messager
-> HomePackageTable -- ^ HPT from last time round (pruned)
-> StableModules -- ^ stable modules (see checkStability)
-> (HscEnv -> IO ()) -- ^ How to clean up unwanted tmp files
- -> [SCC ModSummary] -- ^ Mods to do (the worklist)
+ -> [SCC ModuleGraphNode] -- ^ Mods to do (the worklist)
-> m (SuccessFlag,
- [ModSummary])
+ [ModuleGraphNode])
-- ^ Returns:
--
-- 1. A flag whether the complete upsweep was successful.
@@ -1416,58 +1496,63 @@ upsweep
-- 3. A list of modules which succeeded loading.
upsweep mHscMessage old_hpt stable_mods cleanup sccs = do
- hsc_env <- getSession
(res, done) <- upsweep' old_hpt emptyMG sccs 1 (length sccs)
- (instantiatedUnitsToCheck (hsc_units hsc_env)) done_holes
- return (res, reverse $ mgModSummaries done)
+ return (res, reverse $ mgModSummaries' done)
where
- done_holes = emptyUniqSet
-
- keep_going this_mods old_hpt done mods mod_index nmods uids_to_check done_holes = do
- let sum_deps ms (AcyclicSCC mod) =
- if any (flip elem $ unfilteredEdges False mod) ms
- then mkHomeBuildModule mod:ms
- else ms
+ keep_going
+ :: [NodeKey]
+ -> HomePackageTable
+ -> ModuleGraph
+ -> [SCC ModuleGraphNode]
+ -> Int
+ -> Int
+ -> m (SuccessFlag, ModuleGraph)
+ keep_going this_mods old_hpt done mods mod_index nmods = do
+ let sum_deps ms (AcyclicSCC iuidOrMod) =
+ if any (flip elem $ unfilteredEdges False iuidOrMod) $ ms
+ then mkHomeBuildModule iuidOrMod : ms
+ else ms
sum_deps ms _ = ms
dep_closure = foldl' sum_deps this_mods mods
dropped_ms = drop (length this_mods) (reverse dep_closure)
- prunable (AcyclicSCC mod) = elem (mkHomeBuildModule mod) dep_closure
+ prunable (AcyclicSCC node) = elem (mkHomeBuildModule node) dep_closure
prunable _ = False
mods' = filter (not . prunable) mods
nmods' = nmods - length dropped_ms
when (not $ null dropped_ms) $ do
dflags <- getSessionDynFlags
- liftIO $ fatalErrorMsg dflags (keepGoingPruneErr $ gwib_mod <$> dropped_ms)
- (_, done') <- upsweep' old_hpt done mods' (mod_index+1) nmods' uids_to_check done_holes
+ liftIO $ fatalErrorMsg dflags (keepGoingPruneErr $ dropped_ms)
+ (_, done') <- upsweep' old_hpt done mods' (mod_index+1) nmods'
return (Failed, done')
upsweep'
:: HomePackageTable
-> ModuleGraph
- -> [SCC ModSummary]
+ -> [SCC ModuleGraphNode]
-> Int
-> Int
- -> [Unit]
- -> UniqSet ModuleName
-> m (SuccessFlag, ModuleGraph)
upsweep' _old_hpt done
- [] _ _ uids_to_check _
- = do hsc_env <- getSession
- liftIO . runHsc hsc_env $ mapM_ (ioMsgMaybe . tcRnCheckUnit hsc_env) uids_to_check
- return (Succeeded, done)
+ [] _ _
+ = return (Succeeded, done)
upsweep' _old_hpt done
- (CyclicSCC ms:mods) mod_index nmods uids_to_check done_holes
+ (CyclicSCC ms : mods) mod_index nmods
= do dflags <- getSessionDynFlags
liftIO $ fatalErrorMsg dflags (cyclicModuleErr ms)
if gopt Opt_KeepGoing dflags
then keep_going (mkHomeBuildModule <$> ms) old_hpt done mods mod_index nmods
- uids_to_check done_holes
else return (Failed, done)
upsweep' old_hpt done
- (AcyclicSCC mod:mods) mod_index nmods uids_to_check done_holes
+ (AcyclicSCC (InstantiationNode iuid) : mods) mod_index nmods
+ = do hsc_env <- getSession
+ liftIO $ upsweep_inst hsc_env mHscMessage mod_index nmods iuid
+ upsweep' old_hpt done mods (mod_index+1) nmods
+
+ upsweep' old_hpt done
+ (AcyclicSCC (ModuleNode ems@(ExtendedModSummary mod _)) : mods) mod_index nmods
= do -- putStrLn ("UPSWEEP_MOD: hpt = " ++
-- show (map (moduleUserString.moduleName.mi_module.hm_iface)
-- (moduleEnvElts (hsc_HPT hsc_env)))
@@ -1475,18 +1560,6 @@ upsweep mHscMessage old_hpt stable_mods cleanup sccs = do
hsc_env <- getSession
- -- TODO: Cache this, so that we don't repeatedly re-check
- -- our imports when you run --make.
- let (ready_uids, uids_to_check')
- = partition (\uid -> isEmptyUniqDSet
- (unitFreeModuleHoles uid `uniqDSetMinusUniqSet` done_holes))
- uids_to_check
- done_holes'
- | ms_hsc_src mod == HsigFile
- = addOneToUniqSet done_holes (ms_mod_name mod)
- | otherwise = done_holes
- liftIO . runHsc hsc_env $ mapM_ (ioMsgMaybe . tcRnCheckUnit hsc_env) ready_uids
-
-- Remove unwanted tmp files between compilations
liftIO (cleanup hsc_env)
@@ -1516,8 +1589,7 @@ upsweep mHscMessage old_hpt stable_mods cleanup sccs = do
Nothing -> do
dflags <- getSessionDynFlags
if gopt Opt_KeepGoing dflags
- then keep_going [mkHomeBuildModule mod] old_hpt done mods mod_index nmods
- uids_to_check done_holes
+ then keep_going [NodeKey_Module $ mkHomeBuildModule0 mod] old_hpt done mods mod_index nmods
else return (Failed, done)
Just mod_info -> do
let this_mod = ms_mod_name mod
@@ -1537,7 +1609,7 @@ upsweep mHscMessage old_hpt stable_mods cleanup sccs = do
IsBoot -> old_hpt
NotBoot -> delFromHpt old_hpt this_mod
- done' = extendMG done mod
+ done' = extendMG done ems
-- fixup our HomePackageTable after we've finished compiling
-- a mutually-recursive loop. We have to do this again
@@ -1559,19 +1631,7 @@ upsweep mHscMessage old_hpt stable_mods cleanup sccs = do
, spt <- spts
]
- upsweep' old_hpt1 done' mods (mod_index+1) nmods uids_to_check' done_holes'
-
--- | Return a list of instantiated units to type check from the UnitState.
---
--- Use explicit (instantiated) units as roots and also return their
--- instantiations that are themselves instantiations and so on recursively.
-instantiatedUnitsToCheck :: UnitState -> [Unit]
-instantiatedUnitsToCheck unit_state =
- nubSort $ concatMap goUnit (explicitUnits unit_state)
- where
- goUnit HoleUnit = []
- goUnit (RealUnit _) = []
- goUnit uid@(VirtUnit i) = uid : concatMap (goUnit . moduleUnit . snd) (instUnitInsts i)
+ upsweep' old_hpt1 done' mods (mod_index+1) nmods
maybeGetIfaceDate :: DynFlags -> ModLocation -> IO (Maybe UTCTime)
maybeGetIfaceDate dflags location
@@ -1582,6 +1642,19 @@ maybeGetIfaceDate dflags location
| otherwise
= return Nothing
+upsweep_inst :: HscEnv
+ -> Maybe Messager
+ -> Int -- index of module
+ -> Int -- total number of modules
+ -> InstantiatedUnit
+ -> IO ()
+upsweep_inst hsc_env mHscMessage mod_index nmods iuid = do
+ case mHscMessage of
+ Just hscMessage -> hscMessage hsc_env (mod_index, nmods) MustCompile (InstantiationNode iuid)
+ Nothing -> return ()
+ runHsc hsc_env $ ioMsgMaybe $ tcRnCheckUnit hsc_env $ VirtUnit iuid
+ pure ()
+
-- | Compile a single module. Always produce a Linkable for it if
-- successful. If no compilation happened, return the old Linkable.
upsweep_mod :: HscEnv
@@ -1867,13 +1940,17 @@ reTypecheckLoop hsc_env ms graph
| Just loop <- getModLoop ms mss appearsAsBoot
-- SOME hs-boot files should still
-- get used, just not the loop-closer.
- , let non_boot = filter (\l -> not (isBootSummary l == IsBoot &&
- ms_mod l == ms_mod ms)) loop
+ , let non_boot = flip mapMaybe loop $ \case
+ InstantiationNode _ -> Nothing
+ ModuleNode ems -> do
+ let l = emsModSummary ems
+ guard $ not $ isBootSummary l == IsBoot && ms_mod l == ms_mod ms
+ pure l
= typecheckLoop (hsc_dflags hsc_env) hsc_env (map ms_mod_name non_boot)
| otherwise
= return hsc_env
where
- mss = mgModSummaries graph
+ mss = mgModSummaries' graph
appearsAsBoot = (`elemModuleSet` mgBootModules graph)
-- | Given a non-boot ModSummary @ms@ of a module, for which there exists a
@@ -1914,9 +1991,9 @@ reTypecheckLoop hsc_env ms graph
--
getModLoop
:: ModSummary
- -> [ModSummary]
+ -> [ModuleGraphNode]
-> (Module -> Bool) -- check if a module appears as a boot module in 'graph'
- -> Maybe [ModSummary]
+ -> Maybe [ModuleGraphNode]
getModLoop ms graph appearsAsBoot
| isBootSummary ms == NotBoot
, appearsAsBoot this_mod
@@ -1947,12 +2024,12 @@ typecheckLoop dflags hsc_env mods = do
old_hpt = hsc_HPT hsc_env
hmis = map (expectJust "typecheckLoop" . lookupHpt old_hpt) mods
-reachableBackwards :: ModuleName -> [ModSummary] -> [ModSummary]
+reachableBackwards :: ModuleName -> [ModuleGraphNode] -> [ModuleGraphNode]
reachableBackwards mod summaries
= [ node_payload node | node <- reachableG (transposeG graph) root ]
where -- the rest just sets up the graph:
(graph, lookup_node) = moduleGraphNodes False summaries
- root = expectJust "reachableBackwards" (lookup_node $ GWIB mod IsBoot)
+ root = expectJust "reachableBackwards" (lookup_node $ NodeKey_Module $ GWIB mod IsBoot)
-- ---------------------------------------------------------------------------
--
@@ -1963,7 +2040,7 @@ topSortModuleGraph
-> ModuleGraph
-> Maybe ModuleName
-- ^ Root module name. If @Nothing@, use the full graph.
- -> [SCC ModSummary]
+ -> [SCC ModuleGraphNode]
-- ^ Calculate SCCs of the module graph, possibly dropping the hi-boot nodes
-- The resulting list of strongly-connected-components is in topologically
-- sorted order, starting with the module(s) at the bottom of the
@@ -1982,7 +2059,7 @@ topSortModuleGraph
topSortModuleGraph drop_hs_boot_nodes module_graph mb_root_mod
= map (fmap summaryNodeSummary) $ stronglyConnCompG initial_graph
where
- summaries = mgModSummaries module_graph
+ summaries = mgModSummaries' module_graph
-- stronglyConnCompG flips the original order, so if we reverse
-- the summaries we get a stable topological sort.
(graph, lookup_node) =
@@ -1995,22 +2072,22 @@ topSortModuleGraph drop_hs_boot_nodes module_graph mb_root_mod
-- the specified module. We do this by building a graph with
-- the full set of nodes, and determining the reachable set from
-- the specified node.
- let root | Just node <- lookup_node $ GWIB root_mod NotBoot
+ let root | Just node <- lookup_node $ NodeKey_Module $ GWIB root_mod NotBoot
, graph `hasVertexG` node
= node
| otherwise
= throwGhcException (ProgramError "module does not exist")
in graphFromEdgedVerticesUniq (seq root (reachableG graph root))
-type SummaryNode = Node Int ModSummary
+type SummaryNode = Node Int ModuleGraphNode
summaryNodeKey :: SummaryNode -> Int
summaryNodeKey = node_key
-summaryNodeSummary :: SummaryNode -> ModSummary
+summaryNodeSummary :: SummaryNode -> ModuleGraphNode
summaryNodeSummary = node_payload
--- | Collect the immediate dependencies of a module from its ModSummary,
+-- | Collect the immediate dependencies of a ModuleGraphNode,
-- optionally avoiding hs-boot dependencies.
-- If the drop_hs_boot_nodes flag is False, and if this is a .hs and there is
-- an equivalent .hs-boot, add a link from the former to the latter. This
@@ -2018,68 +2095,102 @@ summaryNodeSummary = node_payload
-- .hs, by introducing a cycle. Additionally, it ensures that we will always
-- process the .hs-boot before the .hs, and so the HomePackageTable will always
-- have the most up to date information.
-unfilteredEdges :: Bool -> ModSummary -> [ModuleNameWithIsBoot]
-unfilteredEdges drop_hs_boot_nodes ms =
- (flip GWIB hs_boot_key . unLoc <$> ms_home_srcimps ms) ++
- (flip GWIB NotBoot . unLoc <$> ms_home_imps ms) ++
- [ GWIB (ms_mod_name ms) IsBoot
- | not $ drop_hs_boot_nodes || ms_hsc_src ms == HsBootFile
- ]
+unfilteredEdges :: Bool -> ModuleGraphNode -> [NodeKey]
+unfilteredEdges drop_hs_boot_nodes = \case
+ InstantiationNode iuid ->
+ NodeKey_Module . flip GWIB NotBoot <$> uniqDSetToList (instUnitHoles iuid)
+ ModuleNode (ExtendedModSummary ms bds) ->
+ (NodeKey_Module . flip GWIB hs_boot_key . unLoc <$> ms_home_srcimps ms) ++
+ (NodeKey_Module . flip GWIB NotBoot . unLoc <$> ms_home_imps ms) ++
+ [ NodeKey_Module $ GWIB (ms_mod_name ms) IsBoot
+ | not $ drop_hs_boot_nodes || ms_hsc_src ms == HsBootFile
+ ] ++
+ [ NodeKey_Unit inst_unit
+ | inst_unit <- bds
+ ]
where
-- Drop hs-boot nodes by using HsSrcFile as the key
hs_boot_key | drop_hs_boot_nodes = NotBoot -- is regular mod or signature
| otherwise = IsBoot
-moduleGraphNodes :: Bool -> [ModSummary]
- -> (Graph SummaryNode, ModuleNameWithIsBoot -> Maybe SummaryNode)
+moduleGraphNodes :: Bool -> [ModuleGraphNode]
+ -> (Graph SummaryNode, NodeKey -> Maybe SummaryNode)
moduleGraphNodes drop_hs_boot_nodes summaries =
(graphFromEdgedVerticesUniq nodes, lookup_node)
where
numbered_summaries = zip summaries [1..]
- lookup_node :: ModuleNameWithIsBoot -> Maybe SummaryNode
- lookup_node mnwib = Map.lookup mnwib node_map
+ lookup_node :: NodeKey -> Maybe SummaryNode
+ lookup_node key = Map.lookup key (unNodeMap node_map)
- lookup_key :: ModuleNameWithIsBoot -> Maybe Int
+ lookup_key :: NodeKey -> Maybe Int
lookup_key = fmap summaryNodeKey . lookup_node
node_map :: NodeMap SummaryNode
- node_map = Map.fromList [ (mkHomeBuildModule s, node)
- | node <- nodes
- , let s = summaryNodeSummary node
- ]
+ node_map = NodeMap $
+ Map.fromList [ (mkHomeBuildModule s, node)
+ | node <- nodes
+ , let s = summaryNodeSummary node
+ ]
-- We use integers as the keys for the SCC algorithm
nodes :: [SummaryNode]
nodes = [ DigraphNode s key $ out_edge_keys $ unfilteredEdges drop_hs_boot_nodes s
| (s, key) <- numbered_summaries
-- Drop the hi-boot ones if told to do so
- , not (isBootSummary s == IsBoot && drop_hs_boot_nodes)
+ , case s of
+ InstantiationNode _ -> True
+ ModuleNode ems -> not $ isBootSummary (emsModSummary ems) == IsBoot && drop_hs_boot_nodes
]
- out_edge_keys :: [ModuleNameWithIsBoot] -> [Int]
+ out_edge_keys :: [NodeKey] -> [Int]
out_edge_keys = mapMaybe lookup_key
-- If we want keep_hi_boot_nodes, then we do lookup_key with
-- IsBoot; else False
--- The nodes of the graph are keyed by (mod, is boot?) pairs
+-- The nodes of the graph are keyed by (mod, is boot?) pairs for the current
+-- modules, and indefinite unit IDs for dependencies which are instantiated with
+-- our holes.
+--
-- NB: hsig files show up as *normal* nodes (not boot!), since they don't
-- participate in cycles (for now)
-type NodeKey = ModuleNameWithIsBoot
-type NodeMap a = Map.Map NodeKey a
-
-msKey :: ModSummary -> NodeKey
-msKey (ModSummary { ms_mod = mod, ms_hsc_src = boot })
- = GWIB
- { gwib_mod = moduleName mod
- , gwib_isBoot = hscSourceToIsBoot boot
- }
+type ModNodeKey = ModuleNameWithIsBoot
+newtype ModNodeMap a = ModNodeMap { unModNodeMap :: Map.Map ModNodeKey a }
+ deriving (Functor, Traversable, Foldable)
+
+emptyModNodeMap :: ModNodeMap a
+emptyModNodeMap = ModNodeMap Map.empty
+
+modNodeMapInsert :: ModNodeKey -> a -> ModNodeMap a -> ModNodeMap a
+modNodeMapInsert k v (ModNodeMap m) = ModNodeMap (Map.insert k v m)
+
+modNodeMapElems :: ModNodeMap a -> [a]
+modNodeMapElems (ModNodeMap m) = Map.elems m
+
+modNodeMapLookup :: ModNodeKey -> ModNodeMap a -> Maybe a
+modNodeMapLookup k (ModNodeMap m) = Map.lookup k m
-mkNodeMap :: [ModSummary] -> NodeMap ModSummary
-mkNodeMap summaries = Map.fromList [ (msKey s, s) | s <- summaries]
+data NodeKey = NodeKey_Unit {-# UNPACK #-} !InstantiatedUnit | NodeKey_Module {-# UNPACK #-} !ModNodeKey
+ deriving (Eq, Ord)
-nodeMapElts :: NodeMap a -> [a]
-nodeMapElts = Map.elems
+newtype NodeMap a = NodeMap { unNodeMap :: Map.Map NodeKey a }
+ deriving (Functor, Traversable, Foldable)
+
+msKey :: ModSummary -> ModNodeKey
+msKey = mkHomeBuildModule0
+
+mkNodeKey :: ModuleGraphNode -> NodeKey
+mkNodeKey = \case
+ InstantiationNode x -> NodeKey_Unit x
+ ModuleNode x -> NodeKey_Module $ mkHomeBuildModule0 (emsModSummary x)
+
+pprNodeKey :: NodeKey -> SDoc
+pprNodeKey (NodeKey_Unit iu) = ppr iu
+pprNodeKey (NodeKey_Module mk) = ppr mk
+
+mkNodeMap :: [ExtendedModSummary] -> ModNodeMap ExtendedModSummary
+mkNodeMap summaries = ModNodeMap $ Map.fromList
+ [ (msKey $ emsModSummary s, s) | s <- summaries]
-- | If there are {-# SOURCE #-} imports between strongly connected
-- components in the topological sort, then those imports can
@@ -2118,16 +2229,17 @@ warnUnnecessarySourceImports sccs = do
-- module, plus one for any hs-boot files. The imports of these nodes
-- are all there, including the imports of non-home-package modules.
downsweep :: HscEnv
- -> [ModSummary] -- Old summaries
+ -> [ExtendedModSummary]
+ -- ^ Old summaries
-> [ModuleName] -- Ignore dependencies on these; treat
-- them as if they were package modules
-> Bool -- True <=> allow multiple targets to have
-- the same module name; this is
-- very useful for ghc -M
- -> IO [Either ErrorMessages ModSummary]
- -- The elts of [ModSummary] all have distinct
- -- (Modules, IsBoot) identifiers, unless the Bool is true
- -- in which case there can be repeats
+ -> IO [Either ErrorMessages ExtendedModSummary]
+ -- The non-error elements of the returned list all have distinct
+ -- (Modules, IsBoot) identifiers, unless the Bool is true in
+ -- which case there can be repeats
downsweep hsc_env old_summaries excl_mods allow_dup_roots
= do
rootSummaries <- mapM getRootSummary roots
@@ -2146,18 +2258,20 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
Interpreter -> enableCodeGenForUnboxedTuplesOrSums default_backend map0
_ -> return map0
if null errs
- then pure $ concat $ nodeMapElts map1
+ then pure $ concat $ modNodeMapElems map1
else pure $ map Left errs
where
- calcDeps = msDeps
+ -- TODO(@Ericson2314): Probably want to include backpack instantiations
+ -- in the map eventually for uniformity
+ calcDeps (ExtendedModSummary ms _bkp_deps) = msDeps ms
dflags = hsc_dflags hsc_env
roots = hsc_targets hsc_env
- old_summary_map :: NodeMap ModSummary
+ old_summary_map :: ModNodeMap ExtendedModSummary
old_summary_map = mkNodeMap old_summaries
- getRootSummary :: Target -> IO (Either ErrorMessages ModSummary)
+ getRootSummary :: Target -> IO (Either ErrorMessages ExtendedModSummary)
getRootSummary (Target (TargetFile file mb_phase) obj_allowed maybe_buf)
= do exists <- liftIO $ doesFileExist file
if exists || isJust maybe_buf
@@ -2179,40 +2293,46 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
-- name, so we have to check that there aren't multiple root files
-- defining the same module (otherwise the duplicates will be silently
-- ignored, leading to confusing behaviour).
- checkDuplicates :: NodeMap [Either ErrorMessages ModSummary] -> IO ()
+ checkDuplicates
+ :: ModNodeMap
+ [Either ErrorMessages
+ ExtendedModSummary]
+ -> IO ()
checkDuplicates root_map
| allow_dup_roots = return ()
| null dup_roots = return ()
- | otherwise = liftIO $ multiRootsErr dflags (head dup_roots)
+ | otherwise = liftIO $ multiRootsErr dflags (emsModSummary <$> head dup_roots)
where
- dup_roots :: [[ModSummary]] -- Each at least of length 2
- dup_roots = filterOut isSingleton $ map rights $ nodeMapElts root_map
+ dup_roots :: [[ExtendedModSummary]] -- Each at least of length 2
+ dup_roots = filterOut isSingleton $ map rights $ modNodeMapElems root_map
loop :: [GenWithIsBoot (Located ModuleName)]
-- Work list: process these modules
- -> NodeMap [Either ErrorMessages ModSummary]
+ -> ModNodeMap [Either ErrorMessages ExtendedModSummary]
-- Visited set; the range is a list because
-- the roots can have the same module names
-- if allow_dup_roots is True
- -> IO (NodeMap [Either ErrorMessages ModSummary])
+ -> IO (ModNodeMap [Either ErrorMessages ExtendedModSummary])
-- The result is the completed NodeMap
loop [] done = return done
loop (s : ss) done
- | Just summs <- Map.lookup key done
+ | Just summs <- modNodeMapLookup key done
= if isSingleton summs then
loop ss done
else
- do { multiRootsErr dflags (rights summs); return Map.empty }
+ do { multiRootsErr dflags (emsModSummary <$> rights summs)
+ ; return (ModNodeMap Map.empty)
+ }
| otherwise
= do mb_s <- summariseModule hsc_env old_summary_map
is_boot wanted_mod True
Nothing excl_mods
case mb_s of
Nothing -> loop ss done
- Just (Left e) -> loop ss (Map.insert key [Left e] done)
+ Just (Left e) -> loop ss (modNodeMapInsert key [Left e] done)
Just (Right s)-> do
new_map <-
- loop (calcDeps s) (Map.insert key [Right s] done)
+ loop (calcDeps s) (modNodeMapInsert key [Right s] done)
loop ss new_map
where
GWIB { gwib_mod = L loc mod, gwib_isBoot = is_boot } = s
@@ -2228,8 +2348,8 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
-- and .o file locations to be temporary files.
-- See Note [-fno-code mode]
enableCodeGenForTH :: HomeUnit -> Backend
- -> NodeMap [Either ErrorMessages ModSummary]
- -> IO (NodeMap [Either ErrorMessages ModSummary])
+ -> ModNodeMap [Either ErrorMessages ExtendedModSummary]
+ -> IO (ModNodeMap [Either ErrorMessages ExtendedModSummary])
enableCodeGenForTH home_unit =
enableCodeGenWhen condition should_modify TFL_CurrentModule TFL_GhcSession
where
@@ -2248,8 +2368,8 @@ enableCodeGenForTH home_unit =
-- This is used in order to load code that uses unboxed tuples
-- or sums into GHCi while still allowing some code to be interpreted.
enableCodeGenForUnboxedTuplesOrSums :: Backend
- -> NodeMap [Either ErrorMessages ModSummary]
- -> IO (NodeMap [Either ErrorMessages ModSummary])
+ -> ModNodeMap [Either ErrorMessages ExtendedModSummary]
+ -> IO (ModNodeMap [Either ErrorMessages ExtendedModSummary])
enableCodeGenForUnboxedTuplesOrSums =
enableCodeGenWhen condition should_modify TFL_GhcSession TFL_CurrentModule
where
@@ -2274,12 +2394,13 @@ enableCodeGenWhen
-> TempFileLifetime
-> TempFileLifetime
-> Backend
- -> NodeMap [Either ErrorMessages ModSummary]
- -> IO (NodeMap [Either ErrorMessages ModSummary])
+ -> ModNodeMap [Either ErrorMessages ExtendedModSummary]
+ -> IO (ModNodeMap [Either ErrorMessages ExtendedModSummary])
enableCodeGenWhen condition should_modify staticLife dynLife bcknd nodemap =
traverse (traverse (traverse enable_code_gen)) nodemap
where
- enable_code_gen ms
+ enable_code_gen :: ExtendedModSummary -> IO ExtendedModSummary
+ enable_code_gen (ExtendedModSummary ms bkp_deps)
| ModSummary
{ ms_mod = ms_mod
, ms_location = ms_location
@@ -2305,22 +2426,23 @@ enableCodeGenWhen condition should_modify staticLife dynLife bcknd nodemap =
then return (ml_hi_file ms_location, ml_obj_file ms_location)
else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags))
<*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags))
- return $
- ms
- { ms_location =
- ms_location {ml_hi_file = hi_file, ml_obj_file = o_file}
- , ms_hspp_opts = updOptLevel 0 $ dflags {backend = bcknd}
- }
- | otherwise = return ms
+ let ms' = ms
+ { ms_location =
+ ms_location {ml_hi_file = hi_file, ml_obj_file = o_file}
+ , ms_hspp_opts = updOptLevel 0 $ dflags {backend = bcknd}
+ }
+ pure (ExtendedModSummary ms' bkp_deps)
+ | otherwise = return (ExtendedModSummary ms bkp_deps)
needs_codegen_set = transitive_deps_set
[ ms
- | mss <- Map.elems nodemap
- , Right ms <- mss
+ | mss <- modNodeMapElems nodemap
+ , Right (ExtendedModSummary { emsModSummary = ms }) <- mss
, condition ms
]
-- find the set of all transitive dependencies of a list of modules.
+ transitive_deps_set :: [ModSummary] -> Set.Set Module
transitive_deps_set modSums = foldl' go Set.empty modSums
where
go marked_mods ms@ModSummary{ms_mod}
@@ -2333,17 +2455,20 @@ enableCodeGenWhen condition should_modify staticLife dynLife bcknd nodemap =
-- means we don't have to think about boot modules here.
| dep <- msDeps ms
, NotBoot == gwib_isBoot dep
- , dep_ms_0 <- toList $ Map.lookup (unLoc <$> dep) nodemap
+ , dep_ms_0 <- toList $ modNodeMapLookup (unLoc <$> dep) nodemap
, dep_ms_1 <- toList $ dep_ms_0
- , dep_ms <- toList $ dep_ms_1
+ , (ExtendedModSummary { emsModSummary = dep_ms }) <- toList $ dep_ms_1
]
new_marked_mods = Set.insert ms_mod marked_mods
in foldl' go new_marked_mods deps
-mkRootMap :: [ModSummary] -> NodeMap [Either ErrorMessages ModSummary]
-mkRootMap summaries = Map.insertListWith (flip (++))
- [ (msKey s, [Right s]) | s <- summaries ]
- Map.empty
+mkRootMap
+ :: [ExtendedModSummary]
+ -> ModNodeMap [Either ErrorMessages ExtendedModSummary]
+mkRootMap summaries = ModNodeMap $ Map.insertListWith
+ (flip (++))
+ [ (msKey $ emsModSummary s, [Right s]) | s <- summaries ]
+ Map.empty
-- | Returns the dependencies of the ModSummary s.
-- A wrinkle is that for a {-# SOURCE #-} import we return
@@ -2379,12 +2504,12 @@ msDeps s = [ d
summariseFile
:: HscEnv
- -> [ModSummary] -- old summaries
+ -> [ExtendedModSummary] -- old summaries
-> FilePath -- source file name
-> Maybe Phase -- start phase
-> Bool -- object code allowed?
-> Maybe (StringBuffer,UTCTime)
- -> IO (Either ErrorMessages ModSummary)
+ -> IO (Either ErrorMessages ExtendedModSummary)
summariseFile hsc_env old_summaries src_fn mb_phase obj_allowed maybe_buf
-- we can use a cached summary if one is available and the
@@ -2392,7 +2517,7 @@ summariseFile hsc_env old_summaries src_fn mb_phase obj_allowed maybe_buf
-- by source file, rather than module name as we do in summarise.
| Just old_summary <- findSummaryBySourceFile old_summaries src_fn
= do
- let location = ms_location old_summary
+ let location = ms_location $ emsModSummary old_summary
dflags = hsc_dflags hsc_env
src_timestamp <- get_src_timestamp
@@ -2441,21 +2566,27 @@ summariseFile hsc_env old_summaries src_fn mb_phase obj_allowed maybe_buf
, nms_preimps = preimps
}
-findSummaryBySourceFile :: [ModSummary] -> FilePath -> Maybe ModSummary
-findSummaryBySourceFile summaries file
- = case [ ms | ms <- summaries, HsSrcFile <- [ms_hsc_src ms],
- expectJust "findSummaryBySourceFile" (ml_hs_file (ms_location ms)) == file ] of
- [] -> Nothing
- (x:_) -> Just x
+findSummaryBySourceFile :: [ExtendedModSummary] -> FilePath -> Maybe ExtendedModSummary
+findSummaryBySourceFile summaries file = case
+ [ ms
+ | ms <- summaries
+ , HsSrcFile <- [ms_hsc_src $ emsModSummary ms]
+ , let derived_file = ml_hs_file $ ms_location $ emsModSummary ms
+ , expectJust "findSummaryBySourceFile" derived_file == file
+ ]
+ of
+ [] -> Nothing
+ (x:_) -> Just x
checkSummaryTimestamp
:: HscEnv -> DynFlags -> Bool -> IsBootInterface
- -> (UTCTime -> IO (Either e ModSummary))
- -> ModSummary -> ModLocation -> UTCTime
- -> IO (Either e ModSummary)
+ -> (UTCTime -> IO (Either e ExtendedModSummary))
+ -> ExtendedModSummary -> ModLocation -> UTCTime
+ -> IO (Either e ExtendedModSummary)
checkSummaryTimestamp
hsc_env dflags obj_allowed is_boot new_summary
- old_summary location src_timestamp
+ (ExtendedModSummary { emsModSummary = old_summary, emsInstantiatedUnits = bkp_deps})
+ location src_timestamp
| ms_hs_date old_summary == src_timestamp &&
not (gopt Opt_ForceRecomp (hsc_dflags hsc_env)) = do
-- update the object-file timestamp
@@ -2476,11 +2607,15 @@ checkSummaryTimestamp
hi_timestamp <- maybeGetIfaceDate dflags location
hie_timestamp <- modificationTimeIfExists (ml_hie_file location)
- return $ Right old_summary
- { ms_obj_date = obj_timestamp
- , ms_iface_date = hi_timestamp
- , ms_hie_date = hie_timestamp
- }
+ return $ Right
+ ( ExtendedModSummary { emsModSummary = old_summary
+ { ms_obj_date = obj_timestamp
+ , ms_iface_date = hi_timestamp
+ , ms_hie_date = hie_timestamp
+ }
+ , emsInstantiatedUnits = bkp_deps
+ }
+ )
| otherwise =
-- source changed: re-summarise.
@@ -2489,25 +2624,26 @@ checkSummaryTimestamp
-- Summarise a module, and pick up source and timestamp.
summariseModule
:: HscEnv
- -> NodeMap ModSummary -- Map of old summaries
+ -> ModNodeMap ExtendedModSummary
+ -- ^ Map of old summaries
-> IsBootInterface -- True <=> a {-# SOURCE #-} import
-> Located ModuleName -- Imported module to be summarised
-> Bool -- object code allowed?
-> Maybe (StringBuffer, UTCTime)
-> [ModuleName] -- Modules to exclude
- -> IO (Maybe (Either ErrorMessages ModSummary)) -- Its new summary
+ -> IO (Maybe (Either ErrorMessages ExtendedModSummary)) -- Its new summary
summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
obj_allowed maybe_buf excl_mods
| wanted_mod `elem` excl_mods
= return Nothing
- | Just old_summary <- Map.lookup
+ | Just old_summary <- modNodeMapLookup
(GWIB { gwib_mod = wanted_mod, gwib_isBoot = is_boot })
old_summary_map
= do -- Find its new timestamp; all the
-- ModSummaries in the old map have valid ml_hs_files
- let location = ms_location old_summary
+ let location = ms_location $ emsModSummary old_summary
src_fn = expectJust "summariseModule" (ml_hs_file location)
-- check the modification time on the source file, and
@@ -2532,7 +2668,7 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
check_timestamp old_summary location src_fn =
checkSummaryTimestamp
hsc_env dflags obj_allowed is_boot
- (new_summary location (ms_mod old_summary) src_fn)
+ (new_summary location (ms_mod $ emsModSummary old_summary) src_fn)
old_summary location
find_it = do
@@ -2629,7 +2765,7 @@ data MakeNewModSummary
, nms_preimps :: PreprocessedImports
}
-makeNewModSummary :: HscEnv -> MakeNewModSummary -> IO ModSummary
+makeNewModSummary :: HscEnv -> MakeNewModSummary -> IO ExtendedModSummary
makeNewModSummary hsc_env MakeNewModSummary{..} = do
let PreprocessedImports{..} = nms_preimps
let dflags = hsc_dflags hsc_env
@@ -2646,24 +2782,30 @@ makeNewModSummary hsc_env MakeNewModSummary{..} = do
hie_timestamp <- modificationTimeIfExists (ml_hie_file nms_location)
extra_sig_imports <- findExtraSigImports hsc_env nms_hsc_src pi_mod_name
- required_by_imports <- implicitRequirements hsc_env pi_theimps
-
- return $ ModSummary
- { ms_mod = nms_mod
- , ms_hsc_src = nms_hsc_src
- , ms_location = nms_location
- , ms_hspp_file = pi_hspp_fn
- , ms_hspp_opts = pi_local_dflags
- , ms_hspp_buf = Just pi_hspp_buf
- , ms_parsed_mod = Nothing
- , ms_srcimps = pi_srcimps
- , ms_textual_imps =
- pi_theimps ++ extra_sig_imports ++ required_by_imports
- , ms_hs_date = nms_src_timestamp
- , ms_iface_date = hi_timestamp
- , ms_hie_date = hie_timestamp
- , ms_obj_date = obj_timestamp
- }
+ (implicit_sigs, inst_deps) <- implicitRequirementsShallow hsc_env pi_theimps
+
+ return $ ExtendedModSummary
+ { emsModSummary =
+ ModSummary
+ { ms_mod = nms_mod
+ , ms_hsc_src = nms_hsc_src
+ , ms_location = nms_location
+ , ms_hspp_file = pi_hspp_fn
+ , ms_hspp_opts = pi_local_dflags
+ , ms_hspp_buf = Just pi_hspp_buf
+ , ms_parsed_mod = Nothing
+ , ms_srcimps = pi_srcimps
+ , ms_textual_imps =
+ pi_theimps ++
+ extra_sig_imports ++
+ ((,) Nothing . noLoc <$> implicit_sigs)
+ , ms_hs_date = nms_src_timestamp
+ , ms_iface_date = hi_timestamp
+ , ms_hie_date = hie_timestamp
+ , ms_obj_date = obj_timestamp
+ }
+ , emsInstantiatedUnits = inst_deps
+ }
getObjTimestamp :: ModLocation -> IsBootInterface -> IO (Maybe UTCTime)
getObjTimestamp location is_boot
@@ -2768,42 +2910,64 @@ multiRootsErr dflags summs@(summ1:_)
mod = ms_mod summ1
files = map (expectJust "checkDup" . ml_hs_file . ms_location) summs
-keepGoingPruneErr :: [ModuleName] -> SDoc
+keepGoingPruneErr :: [NodeKey] -> SDoc
keepGoingPruneErr ms
= vcat (( text "-fkeep-going in use, removing the following" <+>
text "dependencies and continuing:"):
- map (nest 6 . ppr) ms )
+ map (nest 6 . pprNodeKey) ms )
-cyclicModuleErr :: [ModSummary] -> SDoc
+cyclicModuleErr :: [ModuleGraphNode] -> SDoc
-- From a strongly connected component we find
-- a single cycle to report
cyclicModuleErr mss
= ASSERT( not (null mss) )
case findCycle graph of
Nothing -> text "Unexpected non-cycle" <+> ppr mss
- Just path -> vcat [ text "Module imports form a cycle:"
- , nest 2 (show_path path) ]
+ Just path0 -> vcat
+ [ case partitionNodes path0 of
+ ([],_) -> text "Module imports form a cycle:"
+ (_,[]) -> text "Module instantiations form a cycle:"
+ _ -> text "Module imports and instantiations form a cycle:"
+ , nest 2 (show_path path0)]
where
- graph :: [Node NodeKey ModSummary]
- graph = [ DigraphNode ms (msKey ms) (get_deps ms) | ms <- mss]
-
- get_deps :: ModSummary -> [NodeKey]
- get_deps ms =
- [ GWIB { gwib_mod = unLoc m, gwib_isBoot = IsBoot }
- | m <- ms_home_srcimps ms ] ++
- [ GWIB { gwib_mod = unLoc m, gwib_isBoot = NotBoot }
- | m <- ms_home_imps ms ]
-
- show_path [] = panic "show_path"
- show_path [m] = text "module" <+> ppr_ms m
- <+> text "imports itself"
- show_path (m1:m2:ms) = vcat ( nest 7 (text "module" <+> ppr_ms m1)
- : nest 6 (text "imports" <+> ppr_ms m2)
+ graph :: [Node NodeKey ModuleGraphNode]
+ graph =
+ [ DigraphNode
+ { node_payload = ms
+ , node_key = mkNodeKey ms
+ , node_dependencies = get_deps ms
+ }
+ | ms <- mss
+ ]
+
+ get_deps :: ModuleGraphNode -> [NodeKey]
+ get_deps = \case
+ InstantiationNode iuid ->
+ [ NodeKey_Module $ GWIB { gwib_mod = hole, gwib_isBoot = NotBoot }
+ | hole <- uniqDSetToList $ instUnitHoles iuid
+ ]
+ ModuleNode (ExtendedModSummary ms bds) ->
+ [ NodeKey_Module $ GWIB { gwib_mod = unLoc m, gwib_isBoot = IsBoot }
+ | m <- ms_home_srcimps ms ] ++
+ [ NodeKey_Module $ GWIB { gwib_mod = unLoc m, gwib_isBoot = NotBoot }
+ | m <- ms_home_imps ms ] ++
+ [ NodeKey_Unit inst_unit
+ | inst_unit <- bds
+ ]
+
+ show_path :: [ModuleGraphNode] -> SDoc
+ show_path [] = panic "show_path"
+ show_path [m] = ppr_node m <+> text "imports itself"
+ show_path (m1:m2:ms) = vcat ( nest 6 (ppr_node m1)
+ : nest 6 (text "imports" <+> ppr_node m2)
: go ms )
where
- go [] = [text "which imports" <+> ppr_ms m1]
- go (m:ms) = (text "which imports" <+> ppr_ms m) : go ms
+ go [] = [text "which imports" <+> ppr_node m1]
+ go (m:ms) = (text "which imports" <+> ppr_node m) : go ms
+ ppr_node :: ModuleGraphNode -> SDoc
+ ppr_node (ModuleNode m) = text "module" <+> ppr_ms (emsModSummary m)
+ ppr_node (InstantiationNode u) = text "instantiated unit" <+> ppr u
ppr_ms :: ModSummary -> SDoc
ppr_ms ms = quotes (ppr (moduleName (ms_mod ms))) <+>
diff --git a/compiler/GHC/Driver/MakeFile.hs b/compiler/GHC/Driver/MakeFile.hs
index 86262c5ab4..b54bbbea3e 100644
--- a/compiler/GHC/Driver/MakeFile.hs
+++ b/compiler/GHC/Driver/MakeFile.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE CPP #-}
+{-# LANGUAGE LambdaCase #-}
-----------------------------------------------------------------------------
--
@@ -186,7 +187,7 @@ processDeps :: DynFlags
-> [ModuleName]
-> FilePath
-> Handle -- Write dependencies to here
- -> SCC ModSummary
+ -> SCC ModuleGraphNode
-> IO ()
-- Write suitable dependencies to handle
-- Always:
@@ -205,9 +206,17 @@ processDeps :: DynFlags
processDeps dflags _ _ _ _ (CyclicSCC nodes)
= -- There shouldn't be any cycles; report them
- throwGhcExceptionIO (ProgramError (showSDoc dflags $ GHC.cyclicModuleErr nodes))
+ throwGhcExceptionIO $ ProgramError $
+ showSDoc dflags $ GHC.cyclicModuleErr nodes
-processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC node)
+processDeps dflags _ _ _ _ (AcyclicSCC (InstantiationNode node))
+ = -- There shouldn't be any backpack instantiations; report them as well
+ throwGhcExceptionIO $ ProgramError $
+ showSDoc dflags $
+ vcat [ text "Unexpected backpack instantiation in dependency graph while constructing Makefile:"
+ , nest 2 $ ppr node ]
+
+processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode (ExtendedModSummary node _)))
= do { let extra_suffixes = depSuffixes dflags
include_pkg_deps = depIncludePkgDeps dflags
src_file = msHsFilePath node
@@ -371,10 +380,12 @@ dumpModCycles dflags module_graph
| otherwise
= putMsg dflags (hang (text "Module cycles found:") 2 pp_cycles)
where
+ topoSort = filterToposortToModules $
+ GHC.topSortModuleGraph True module_graph Nothing
cycles :: [[ModSummary]]
cycles =
- [ c | CyclicSCC c <- GHC.topSortModuleGraph True module_graph Nothing ]
+ [ c | CyclicSCC c <- topoSort ]
pp_cycles = vcat [ (text "---------- Cycle" <+> int n <+> ptext (sLit "----------"))
$$ pprCycle c $$ blankLine
@@ -402,8 +413,8 @@ pprCycle summaries = pp_group (CyclicSCC summaries)
loop_breaker = head boot_only
all_others = tail boot_only ++ others
- groups =
- GHC.topSortModuleGraph True (mkModuleGraph all_others) Nothing
+ groups = filterToposortToModules $
+ GHC.topSortModuleGraph True (mkModuleGraph $ extendModSummaryNoDeps <$> all_others) Nothing
pp_ms summary = text mod_str <> text (take (20 - length mod_str) (repeat ' '))
<+> (pp_imps empty (map snd (ms_imps summary)) $$
diff --git a/compiler/GHC/Runtime/Eval.hs b/compiler/GHC/Runtime/Eval.hs
index 24aed42125..d1cc9e56c1 100644
--- a/compiler/GHC/Runtime/Eval.hs
+++ b/compiler/GHC/Runtime/Eval.hs
@@ -108,6 +108,7 @@ import GHC.Types.Unique.Supply
import GHC.Types.TyThing
import GHC.Unit
+import GHC.Unit.Module.Graph
import GHC.Unit.Module.ModIface
import GHC.Unit.Module.ModSummary
import GHC.Unit.Home.ModInfo
@@ -1214,7 +1215,8 @@ showModule mod_summary =
withSession $ \hsc_env -> do
interpreted <- moduleIsBootOrNotObjectLinkable mod_summary
let dflags = hsc_dflags hsc_env
- return (showSDoc dflags $ showModMsg dflags interpreted mod_summary)
+ -- extendModSummaryNoDeps because the message doesn't look at the deps
+ return (showSDoc dflags $ showModMsg dflags interpreted (ModuleNode (extendModSummaryNoDeps mod_summary)))
moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool
moduleIsBootOrNotObjectLinkable mod_summary = withSession $ \hsc_env ->
diff --git a/compiler/GHC/Tc/Utils/Backpack.hs b/compiler/GHC/Tc/Utils/Backpack.hs
index c1888c7f36..137fbaeb3a 100644
--- a/compiler/GHC/Tc/Utils/Backpack.hs
+++ b/compiler/GHC/Tc/Utils/Backpack.hs
@@ -8,6 +8,7 @@ module GHC.Tc.Utils.Backpack (
findExtraSigImports,
implicitRequirements',
implicitRequirements,
+ implicitRequirementsShallow,
checkUnit,
tcRnCheckUnit,
tcRnMergeSignatures,
@@ -47,14 +48,14 @@ import GHC.Unit.Module.Imported
import GHC.Unit.Module.Deps
import GHC.Tc.Gen.Export
+import GHC.Tc.Solver
import GHC.Tc.TyCl.Utils
+import GHC.Tc.Types.Constraint
+import GHC.Tc.Types.Origin
import GHC.Tc.Utils.Monad
import GHC.Tc.Utils.Instantiate
import GHC.Tc.Utils.TcMType
import GHC.Tc.Utils.TcType
-import GHC.Tc.Solver
-import GHC.Tc.Types.Constraint
-import GHC.Tc.Types.Origin
import GHC.Hs
@@ -85,7 +86,6 @@ import GHC.Data.Maybe
import Control.Monad
import Data.List (find)
-import qualified Data.Map as Map
import {-# SOURCE #-} GHC.Tc.Module
@@ -247,19 +247,6 @@ check_inst sig_inst = do
(implic, _) <- buildImplicationFor tclvl skol_info tvs_skols [] unsolved
reportAllUnsolved (mkImplicWC implic)
--- | Return this list of requirement interfaces that need to be merged
--- to form @mod_name@, or @[]@ if this is not a requirement.
-requirementMerges :: UnitState -> ModuleName -> [InstantiatedModule]
-requirementMerges unit_state mod_name =
- fmap fixupModule $ fromMaybe [] (Map.lookup mod_name (requirementContext unit_state))
- where
- -- update IndefUnitId ppr info as they may have changed since the
- -- time the IndefUnitId was created
- fixupModule (Module iud name) = Module iud' name
- where
- iud' = iud { instUnitInstanceOf = cid }
- cid = instUnitInstanceOf iud
-
-- | For a module @modname@ of type 'HscSource', determine the list
-- of extra "imports" of other requirements which should be considered part of
-- the import of the requirement, because it transitively depends on those
@@ -267,12 +254,12 @@ requirementMerges unit_state mod_name =
-- is something like this:
--
-- unit p where
--- signature A
--- signature B
--- import A
+-- signature X
+-- signature Y
+-- import X
--
-- unit q where
--- dependency p[A=\<A>,B=\<B>]
+-- dependency p[X=\<A>,Y=\<B>]
-- signature A
-- signature B
--
@@ -306,7 +293,7 @@ findExtraSigImports hsc_env hsc_src modname = do
| mod_name <- uniqDSetToList extra_requirements ]
-- A version of 'implicitRequirements'' which is more friendly
--- for "GHC.Driver.Make" and "GHC.Tc.Module".
+-- for "GHC.Tc.Module".
implicitRequirements :: HscEnv
-> [(Maybe FastString, Located ModuleName)]
-> IO [(Maybe FastString, Located ModuleName)]
@@ -316,7 +303,7 @@ implicitRequirements hsc_env normal_imports
-- Given a list of 'import M' statements in a module, figure out
-- any extra implicit requirement imports they may have. For
--- example, if they 'import M' and M resolves to p[A=<B>], then
+-- example, if they 'import M' and M resolves to p[A=<B>,C=D], then
-- they actually also import the local requirement B.
implicitRequirements' :: HscEnv
-> [(Maybe FastString, Located ModuleName)]
@@ -331,6 +318,28 @@ implicitRequirements' hsc_env normal_imports
_ -> return []
where home_unit = hsc_home_unit hsc_env
+-- | Like @implicitRequirements'@, but returns either the module name, if it is
+-- a free hole, or the instantiated unit the imported module is from, so that
+-- that instantiated unit can be processed and via the batch mod graph (rather
+-- than a transitive closure done here) all the free holes are still reachable.
+implicitRequirementsShallow
+ :: HscEnv
+ -> [(Maybe FastString, Located ModuleName)]
+ -> IO ([ModuleName], [InstantiatedUnit])
+implicitRequirementsShallow hsc_env normal_imports = go ([], []) normal_imports
+ where
+ go acc [] = pure acc
+ go (accL, accR) ((mb_pkg, L _ imp):imports) = do
+ found <- findImportedModule hsc_env imp mb_pkg
+ let acc' = case found of
+ Found _ mod | not (isHomeModule (hsc_home_unit hsc_env) mod) ->
+ case moduleUnit mod of
+ HoleUnit -> (moduleName mod : accL, accR)
+ RealUnit _ -> (accL, accR)
+ VirtUnit u -> (accL, u:accR)
+ _ -> (accL, accR)
+ go acc' imports
+
-- | Given a 'Unit', make sure it is well typed. This is because
-- unit IDs come from Cabal, which does not know if things are well-typed or
-- not; a component may have been filled with implementations for the holes
diff --git a/compiler/GHC/Unit/Module/Graph.hs b/compiler/GHC/Unit/Module/Graph.hs
index faa3ae9b1a..5b5d152711 100644
--- a/compiler/GHC/Unit/Module/Graph.hs
+++ b/compiler/GHC/Unit/Module/Graph.hs
@@ -1,17 +1,26 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
module GHC.Unit.Module.Graph
( ModuleGraph
+ , ModuleGraphNode(..)
, emptyMG
, mkModuleGraph
+ , mkModuleGraph'
, extendMG
+ , extendMGInst
+ , extendMG'
+ , filterToposortToModules
, mapMG
, mgModSummaries
+ , mgModSummaries'
+ , mgExtendedModSummaries
, mgElemModule
, mgLookupModule
, mgBootModules
, needsTemplateHaskellOrQQ
, isTemplateHaskellOrQQNonBoot
+ , showModMsg
)
where
@@ -19,21 +28,50 @@ import GHC.Prelude
import qualified GHC.LanguageExtensions as LangExt
+import GHC.Data.Maybe
+import GHC.Data.Graph.Directed ( SCC(..) )
+
+import GHC.Driver.Backend
+import GHC.Driver.Ppr
import GHC.Driver.Session
+import GHC.Types.SourceFile ( hscSourceString )
+
import GHC.Unit.Module.ModSummary
import GHC.Unit.Module.Env
import GHC.Unit.Types
-
-
--- | A ModuleGraph contains all the nodes from the home package (only).
--- There will be a node for each source module, plus a node for each hi-boot
--- module.
+import GHC.Utils.Outputable
+
+import System.FilePath
+
+-- | A '@ModuleGraphNode@' is a node in the '@ModuleGraph@'.
+-- Edges between nodes mark dependencies arising from module imports
+-- and dependencies arising from backpack instantiations.
+data ModuleGraphNode
+ -- | Instantiation nodes track the instantiation of other units
+ -- (backpack dependencies) with the holes (signatures) of the current package.
+ = InstantiationNode InstantiatedUnit
+ -- | There is a module summary node for each module, signature, and boot module being built.
+ | ModuleNode ExtendedModSummary
+
+instance Outputable ModuleGraphNode where
+ ppr = \case
+ InstantiationNode iuid -> ppr iuid
+ ModuleNode ems -> ppr ems
+
+-- | A '@ModuleGraph@' contains all the nodes from the home package (only). See
+-- '@ModuleGraphNode@' for information about the nodes.
+--
+-- Modules need to be compiled. hs-boots need to be typechecked before
+-- the associated "real" module so modules with {-# SOURCE #-} imports can be
+-- built. Instantiations also need to be typechecked to ensure that the module
+-- fits the signature. Substantiation typechecking is roughly comparable to the
+-- check that the module and its hs-boot agree.
--
-- The graph is not necessarily stored in topologically-sorted order. Use
-- 'GHC.topSortModuleGraph' and 'GHC.Data.Graph.Directed.flattenSCC' to achieve this.
data ModuleGraph = ModuleGraph
- { mg_mss :: [ModSummary]
+ { mg_mss :: [ModuleGraphNode]
, mg_non_boot :: ModuleEnv ModSummary
-- a map of all non-boot ModSummaries keyed by Modules
, mg_boot :: ModuleSet
@@ -56,7 +94,9 @@ needsTemplateHaskellOrQQ mg = mg_needs_th_or_qq mg
-- To preserve invariants 'f' can't change the isBoot status.
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
mapMG f mg@ModuleGraph{..} = mg
- { mg_mss = map f mg_mss
+ { mg_mss = flip fmap mg_mss $ \case
+ InstantiationNode iuid -> InstantiationNode iuid
+ ModuleNode (ExtendedModSummary ms bds) -> ModuleNode (ExtendedModSummary (f ms) bds)
, mg_non_boot = mapModuleEnv f mg_non_boot
}
@@ -64,7 +104,13 @@ mgBootModules :: ModuleGraph -> ModuleSet
mgBootModules ModuleGraph{..} = mg_boot
mgModSummaries :: ModuleGraph -> [ModSummary]
-mgModSummaries = mg_mss
+mgModSummaries mg = [ m | ModuleNode (ExtendedModSummary m _) <- mgModSummaries' mg ]
+
+mgExtendedModSummaries :: ModuleGraph -> [ExtendedModSummary]
+mgExtendedModSummaries mg = [ ems | ModuleNode ems <- mgModSummaries' mg ]
+
+mgModSummaries' :: ModuleGraph -> [ModuleGraphNode]
+mgModSummaries' = mg_mss
mgElemModule :: ModuleGraph -> Module -> Bool
mgElemModule ModuleGraph{..} m = elemModuleEnv m mg_non_boot
@@ -82,11 +128,11 @@ isTemplateHaskellOrQQNonBoot ms =
|| xopt LangExt.QuasiQuotes (ms_hspp_opts ms)) &&
(isBootSummary ms == NotBoot)
--- | Add a ModSummary to ModuleGraph. Assumes that the new ModSummary is
+-- | Add an ExtendedModSummary to ModuleGraph. Assumes that the new ModSummary is
-- not an element of the ModuleGraph.
-extendMG :: ModuleGraph -> ModSummary -> ModuleGraph
-extendMG ModuleGraph{..} ms = ModuleGraph
- { mg_mss = ms:mg_mss
+extendMG :: ModuleGraph -> ExtendedModSummary -> ModuleGraph
+extendMG ModuleGraph{..} ems@(ExtendedModSummary ms _) = ModuleGraph
+ { mg_mss = ModuleNode ems : mg_mss
, mg_non_boot = case isBootSummary ms of
IsBoot -> mg_non_boot
NotBoot -> extendModuleEnv mg_non_boot (ms_mod ms) ms
@@ -96,6 +142,67 @@ extendMG ModuleGraph{..} ms = ModuleGraph
, mg_needs_th_or_qq = mg_needs_th_or_qq || isTemplateHaskellOrQQNonBoot ms
}
-mkModuleGraph :: [ModSummary] -> ModuleGraph
+extendMGInst :: ModuleGraph -> InstantiatedUnit -> ModuleGraph
+extendMGInst mg depUnitId = mg
+ { mg_mss = InstantiationNode depUnitId : mg_mss mg
+ }
+
+extendMG' :: ModuleGraph -> ModuleGraphNode -> ModuleGraph
+extendMG' mg = \case
+ InstantiationNode depUnitId -> extendMGInst mg depUnitId
+ ModuleNode ems -> extendMG mg ems
+
+mkModuleGraph :: [ExtendedModSummary] -> ModuleGraph
mkModuleGraph = foldr (flip extendMG) emptyMG
+mkModuleGraph' :: [ModuleGraphNode] -> ModuleGraph
+mkModuleGraph' = foldr (flip extendMG') emptyMG
+
+-- | This function filters out all the instantiation nodes from each SCC of a
+-- topological sort. Use this with care, as the resulting "strongly connected components"
+-- may not really be strongly connected in a direct way, as instantiations have been
+-- removed. It would probably be best to eliminate uses of this function where possible.
+filterToposortToModules
+ :: [SCC ModuleGraphNode] -> [SCC ModSummary]
+filterToposortToModules = mapMaybe $ mapMaybeSCC $ \case
+ InstantiationNode _ -> Nothing
+ ModuleNode (ExtendedModSummary node _) -> Just node
+ where
+ -- This higher order function is somewhat bogus,
+ -- as the definition of "strongly connected component"
+ -- is not necessarily respected.
+ mapMaybeSCC :: (a -> Maybe b) -> SCC a -> Maybe (SCC b)
+ mapMaybeSCC f = \case
+ AcyclicSCC a -> AcyclicSCC <$> f a
+ CyclicSCC as -> case mapMaybe f as of
+ [] -> Nothing
+ [a] -> Just $ AcyclicSCC a
+ as -> Just $ CyclicSCC as
+
+showModMsg :: DynFlags -> Bool -> ModuleGraphNode -> SDoc
+showModMsg _ _ (InstantiationNode indef_unit) =
+ ppr $ instUnitInstanceOf indef_unit
+showModMsg dflags recomp (ModuleNode (ExtendedModSummary mod_summary _)) =
+ if gopt Opt_HideSourcePaths dflags
+ then text mod_str
+ else hsep $
+ [ text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' ')
+ , char '('
+ , text (op $ msHsFilePath mod_summary) <> char ','
+ ] ++
+ if gopt Opt_BuildDynamicToo dflags
+ then [ text obj_file <> char ','
+ , text dyn_file
+ , char ')'
+ ]
+ else [ text obj_file, char ')' ]
+ where
+ op = normalise
+ mod = moduleName (ms_mod mod_summary)
+ mod_str = showPpr dflags mod ++ hscSourceString (ms_hsc_src mod_summary)
+ dyn_file = op $ msDynObjFilePath mod_summary dflags
+ obj_file = case backend dflags of
+ Interpreter | recomp -> "interpreted"
+ NoBackend -> "nothing"
+ _ -> (op $ msObjFilePath mod_summary)
+
diff --git a/compiler/GHC/Unit/Module/ModSummary.hs b/compiler/GHC/Unit/Module/ModSummary.hs
index a0b42fc2a4..e9106d44eb 100644
--- a/compiler/GHC/Unit/Module/ModSummary.hs
+++ b/compiler/GHC/Unit/Module/ModSummary.hs
@@ -1,7 +1,11 @@
+{-# LANGUAGE LambdaCase #-}
+
-- | A ModSummary is a node in the compilation manager's dependency graph
-- (ModuleGraph)
module GHC.Unit.Module.ModSummary
- ( ModSummary (..)
+ ( ExtendedModSummary (..)
+ , extendModSummaryNoDeps
+ , ModSummary (..)
, ms_installed_mod
, ms_mod_name
, ms_imps
@@ -13,7 +17,6 @@ module GHC.Unit.Module.ModSummary
, msObjFilePath
, msDynObjFilePath
, isBootSummary
- , showModMsg
, findTarget
)
where
@@ -22,9 +25,7 @@ import GHC.Prelude
import GHC.Hs
-import GHC.Driver.Ppr
import GHC.Driver.Session
-import GHC.Driver.Backend
import GHC.Unit.Types
import GHC.Unit.Module
@@ -40,9 +41,24 @@ import GHC.Data.StringBuffer ( StringBuffer )
import GHC.Utils.Outputable
import Data.Time
-import System.FilePath
--- | A single node in a 'ModuleGraph'. The nodes of the module graph
+-- | Enrichment of 'ModSummary' with backpack dependencies
+data ExtendedModSummary = ExtendedModSummary
+ { emsModSummary :: {-# UNPACK #-} !ModSummary
+ , emsInstantiatedUnits :: [InstantiatedUnit]
+ -- ^ Extra backpack deps
+ -- NB: This is sometimes left empty in situations where the instantiated units
+ -- would not be used. See call sites of 'extendModSummaryNoDeps'.
+ }
+
+instance Outputable ExtendedModSummary where
+ ppr = \case
+ ExtendedModSummary ms bds -> ppr ms <+> ppr bds
+
+extendModSummaryNoDeps :: ModSummary -> ExtendedModSummary
+extendModSummaryNoDeps ms = ExtendedModSummary ms []
+
+-- | Data for a module node in a 'ModuleGraph'. Module nodes of the module graph
-- are one of:
--
-- * A regular Haskell source module
@@ -53,7 +69,7 @@ data ModSummary
ms_mod :: Module,
-- ^ Identity of the module
ms_hsc_src :: HscSource,
- -- ^ The module source either plain Haskell or hs-boot
+ -- ^ The module source either plain Haskell, hs-boot, or hsig
ms_location :: ModLocation,
-- ^ Location of the various files belonging to the module
ms_hs_date :: UTCTime,
@@ -150,31 +166,6 @@ instance Outputable ModSummary where
char '}'
]
-showModMsg :: DynFlags -> Bool -> ModSummary -> SDoc
-showModMsg dflags recomp mod_summary =
- if gopt Opt_HideSourcePaths dflags
- then text mod_str
- else hsep $
- [ text (mod_str ++ replicate (max 0 (16 - length mod_str)) ' ')
- , char '('
- , text (op $ msHsFilePath mod_summary) <> char ','
- ] ++
- if gopt Opt_BuildDynamicToo dflags
- then [ text obj_file <> char ','
- , text dyn_file
- , char ')'
- ]
- else [ text obj_file, char ')' ]
- where
- op = normalise
- mod = moduleName (ms_mod mod_summary)
- mod_str = showPpr dflags mod ++ hscSourceString (ms_hsc_src mod_summary)
- dyn_file = op $ msDynObjFilePath mod_summary dflags
- obj_file = case backend dflags of
- Interpreter | recomp -> "interpreted"
- NoBackend -> "nothing"
- _ -> (op $ msObjFilePath mod_summary)
-
findTarget :: ModSummary -> [Target] -> Maybe Target
findTarget ms ts =
case filter (matches ms) ts of
@@ -188,3 +179,5 @@ findTarget ms ts =
= f == f'
_ `matches` _
= False
+
+
diff --git a/compiler/GHC/Unit/State.hs b/compiler/GHC/Unit/State.hs
index 1aabfb10c2..ab76ad2426 100644
--- a/compiler/GHC/Unit/State.hs
+++ b/compiler/GHC/Unit/State.hs
@@ -35,6 +35,7 @@ module GHC.Unit.State (
lookupModuleInAllUnits,
lookupModuleWithSuggestions,
lookupPluginModuleWithSuggestions,
+ requirementMerges,
LookupResult(..),
ModuleSuggestion(..),
ModuleOrigin(..),
@@ -1963,6 +1964,19 @@ instance Outputable UnitErr where
ppr_reason (p, reason) =
pprReason (ppr (unitId p) <+> text "is") reason
+-- | Return this list of requirement interfaces that need to be merged
+-- to form @mod_name@, or @[]@ if this is not a requirement.
+requirementMerges :: UnitState -> ModuleName -> [InstantiatedModule]
+requirementMerges pkgstate mod_name =
+ fmap fixupModule $ fromMaybe [] (Map.lookup mod_name (requirementContext pkgstate))
+ where
+ -- update IndefUnitId ppr info as they may have changed since the
+ -- time the IndefUnitId was created
+ fixupModule (Module iud name) = Module iud' name
+ where
+ iud' = iud { instUnitInstanceOf = cid' }
+ cid' = instUnitInstanceOf iud
+
-- -----------------------------------------------------------------------------
-- | Pretty-print a UnitId for the user.
diff --git a/compiler/GHC/Unit/Types.hs b/compiler/GHC/Unit/Types.hs
index b2f3ce0c50..57dcddef6b 100644
--- a/compiler/GHC/Unit/Types.hs
+++ b/compiler/GHC/Unit/Types.hs
@@ -676,5 +676,5 @@ instance Binary a => Binary (GenWithIsBoot a) where
instance Outputable a => Outputable (GenWithIsBoot a) where
ppr (GWIB { gwib_mod, gwib_isBoot }) = hsep $ ppr gwib_mod : case gwib_isBoot of
- IsBoot -> []
- NotBoot -> [text "{-# SOURCE #-}"]
+ IsBoot -> [ text "{-# SOURCE #-}" ]
+ NotBoot -> []
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index 152017de38..4a1b91a9fc 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -76,6 +76,7 @@ import qualified GHC.Parser.Lexer as Lexer
import GHC.Unit
import GHC.Unit.State
import GHC.Unit.Finder as Finder
+import GHC.Unit.Module.Graph (filterToposortToModules)
import GHC.Unit.Module.ModSummary
import GHC.Data.StringBuffer
@@ -1632,8 +1633,9 @@ chooseEditFile =
graph <- GHC.getModuleGraph
failed_graph <-
- GHC.mkModuleGraph <$> filterM hasFailed (GHC.mgModSummaries graph)
- let order g = flattenSCCs $ GHC.topSortModuleGraph True g Nothing
+ GHC.mkModuleGraph . fmap extendModSummaryNoDeps <$> filterM hasFailed (GHC.mgModSummaries graph)
+ let order g = flattenSCCs $ filterToposortToModules $
+ GHC.topSortModuleGraph True g Nothing
pick xs = case xs of
x : _ -> GHC.ml_hs_file (GHC.ms_location x)
_ -> Nothing
@@ -2018,8 +2020,9 @@ setContextAfterLoad keep_ctxt ms = do
targets <- GHC.getTargets
case [ m | Just m <- map (findTarget ms) targets ] of
[] ->
- let graph = GHC.mkModuleGraph ms
- graph' = flattenSCCs (GHC.topSortModuleGraph True graph Nothing)
+ let graph = GHC.mkModuleGraph $ extendModSummaryNoDeps <$> ms
+ graph' = flattenSCCs $ filterToposortToModules $
+ GHC.topSortModuleGraph True graph Nothing
in load_this (last graph')
(m:_) ->
load_this m
diff --git a/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout b/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout
index 2f17fdffcd..e4c791fc0e 100644
--- a/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout
+++ b/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout
@@ -4,3 +4,4 @@ for bkpcabal01-0.1.0.0..
Preprocessing library 'q' for bkpcabal01-0.1.0.0..
Building library 'q' instantiated with H = <H>
for bkpcabal01-0.1.0.0..
+[2 of 2] Instantiating bkpcabal01-0.1.0.0-8qvodD6NJy6K0RGaf4qK7Y-p
diff --git a/testsuite/tests/backpack/reexport/bkpreex01.stderr b/testsuite/tests/backpack/reexport/bkpreex01.stderr
index ac80b79800..43d54e7db7 100644
--- a/testsuite/tests/backpack/reexport/bkpreex01.stderr
+++ b/testsuite/tests/backpack/reexport/bkpreex01.stderr
@@ -1,6 +1,7 @@
[1 of 2] Processing h
[1 of 1] Compiling H[sig] ( h/H.hsig, nothing )
[2 of 2] Processing p
- [1 of 3] Compiling B ( p/B.hs, nothing )
- [2 of 3] Compiling H[sig] ( p/H.hsig, nothing )
- [3 of 3] Compiling A ( p/A.hs, nothing )
+ [1 of 4] Compiling B ( p/B.hs, nothing )
+ [2 of 4] Compiling H[sig] ( p/H.hsig, nothing )
+ [3 of 4] Compiling A ( p/A.hs, nothing )
+ [4 of 4] Instantiating h
diff --git a/testsuite/tests/backpack/reexport/bkpreex02.stderr b/testsuite/tests/backpack/reexport/bkpreex02.stderr
index 8ae6714f33..97d5e44b6b 100644
--- a/testsuite/tests/backpack/reexport/bkpreex02.stderr
+++ b/testsuite/tests/backpack/reexport/bkpreex02.stderr
@@ -5,9 +5,10 @@
Instantiating timpl
[1 of 1] Compiling TImpl ( timpl/TImpl.hs, nothing )
[3 of 5] Processing q
- [1 of 3] Compiling T[sig] ( q/T.hsig, nothing )
- [2 of 3] Compiling H[sig] ( q/H.hsig, nothing )
- [3 of 3] Compiling A ( q/A.hs, nothing )
+ [1 of 4] Compiling T[sig] ( q/T.hsig, nothing )
+ [2 of 4] Compiling H[sig] ( q/H.hsig, nothing )
+ [3 of 4] Compiling A ( q/A.hs, nothing )
+ [4 of 4] Instantiating p
[4 of 5] Processing r-impl
Instantiating r-impl
[1 of 1] Including timpl
@@ -22,6 +23,8 @@
Instantiating p[H=r-impl:H,T=r-impl:T]
[1 of 2] Compiling T[sig] ( p/T.hsig, nothing )
[2 of 2] Compiling H[sig] ( p/H.hsig, nothing )
- [1 of 3] Compiling T[sig] ( q/T.hsig, nothing )
- [2 of 3] Compiling H[sig] ( q/H.hsig, nothing )
- [3 of 3] Compiling A ( q/A.hs, nothing )
+ [1 of 4] Compiling T[sig] ( q/T.hsig, nothing )
+ [2 of 4] Compiling H[sig] ( q/H.hsig, nothing )
+ [3 of 4] Compiling A ( q/A.hs, nothing )
+ [4 of 4] Instantiating p
+ [1 of 1] Instantiating q
diff --git a/testsuite/tests/backpack/reexport/bkpreex06.stderr b/testsuite/tests/backpack/reexport/bkpreex06.stderr
index 225a8aacc8..6b8b2978b7 100644
--- a/testsuite/tests/backpack/reexport/bkpreex06.stderr
+++ b/testsuite/tests/backpack/reexport/bkpreex06.stderr
@@ -4,5 +4,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A2[sig] ( q/A2.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling A1[sig] ( r/A1.hsig, nothing )
- [2 of 2] Compiling A2[sig] ( r/A2.hsig, nothing )
+ [1 of 4] Compiling A1[sig] ( r/A1.hsig, nothing )
+ [2 of 4] Compiling A2[sig] ( r/A2.hsig, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
diff --git a/testsuite/tests/backpack/reexport/bkpreex08.stderr b/testsuite/tests/backpack/reexport/bkpreex08.stderr
index 41983efaed..ce8f6df39a 100644
--- a/testsuite/tests/backpack/reexport/bkpreex08.stderr
+++ b/testsuite/tests/backpack/reexport/bkpreex08.stderr
@@ -4,5 +4,6 @@
[2 of 3] Processing p2
[1 of 1] Compiling A[sig] ( p2/A.hsig, nothing )
[3 of 3] Processing p
- [1 of 2] Compiling A[sig] ( p/A.hsig, nothing )
- [2 of 2] Compiling M ( p/M.hs, nothing )
+ [1 of 3] Compiling A[sig] ( p/A.hsig, nothing )
+ [2 of 3] Compiling M ( p/M.hs, nothing )
+ [3 of 3] Instantiating p2
diff --git a/testsuite/tests/backpack/reexport/bkpreex09.stderr b/testsuite/tests/backpack/reexport/bkpreex09.stderr
index d4bedc39f5..f0af09ac03 100644
--- a/testsuite/tests/backpack/reexport/bkpreex09.stderr
+++ b/testsuite/tests/backpack/reexport/bkpreex09.stderr
@@ -1,5 +1,6 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
- [2 of 2] Compiling M ( q/M.hs, nothing )
+ [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 3] Compiling M ( q/M.hs, nothing )
+ [3 of 3] Instantiating p
diff --git a/testsuite/tests/backpack/reexport/bkpreex10.stderr b/testsuite/tests/backpack/reexport/bkpreex10.stderr
index d4bedc39f5..f0af09ac03 100644
--- a/testsuite/tests/backpack/reexport/bkpreex10.stderr
+++ b/testsuite/tests/backpack/reexport/bkpreex10.stderr
@@ -1,5 +1,6 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
- [2 of 2] Compiling M ( q/M.hs, nothing )
+ [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 3] Compiling M ( q/M.hs, nothing )
+ [3 of 3] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/T13140.stderr b/testsuite/tests/backpack/should_compile/T13140.stderr
index c40b6bc1df..d15a891968 100644
--- a/testsuite/tests/backpack/should_compile/T13140.stderr
+++ b/testsuite/tests/backpack/should_compile/T13140.stderr
@@ -20,9 +20,12 @@
[3 of 3] Including p[A=q3:A]
Instantiating p[A=q3:A]
[1 of 1] Compiling A[sig] ( p/A.hsig, T13140.out/p/p-200ijkYDy133WhdgYYHZ24/A.o )
+ [1 of 1] Instantiating p
[6 of 7] Processing p2
[1 of 2] Compiling A[sig] ( p2/A.hsig, nothing )
[2 of 2] Compiling M ( p2/M.hs, nothing )
[7 of 7] Processing p3
- [1 of 2] Compiling A[sig] ( p3/A.hsig, nothing )
- [2 of 2] Compiling M2 ( p3/M2.hs, nothing )
+ [1 of 4] Compiling A[sig] ( p3/A.hsig, nothing )
+ [2 of 4] Compiling M2 ( p3/M2.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating p2
diff --git a/testsuite/tests/backpack/should_compile/T13214.stderr b/testsuite/tests/backpack/should_compile/T13214.stderr
index dea6d06ff4..fc07a2511a 100644
--- a/testsuite/tests/backpack/should_compile/T13214.stderr
+++ b/testsuite/tests/backpack/should_compile/T13214.stderr
@@ -7,12 +7,15 @@
[1 of 2] Compiling A ( q/A.hs, T13214.out/q/A.o )
[2 of 2] Compiling A2 ( q/A2.hs, T13214.out/q/A2.o )
[3 of 5] Processing r1
- [1 of 2] Compiling H[sig] ( r1/H.hsig, nothing )
- [2 of 2] Compiling C ( r1/C.hs, nothing )
+ [1 of 3] Compiling H[sig] ( r1/H.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Compiling C ( r1/C.hs, nothing )
[4 of 5] Processing r2
- [1 of 2] Compiling H[sig] ( r2/H.hsig, nothing )
- [2 of 2] Compiling C ( r2/C.hs, nothing )
+ [1 of 3] Compiling H[sig] ( r2/H.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Compiling C ( r2/C.hs, nothing )
[5 of 5] Processing r3
- [1 of 3] Compiling X[sig] ( r3/X.hsig, nothing )
- [2 of 3] Compiling H[sig] ( r3/H.hsig, nothing )
- [3 of 3] Compiling D ( r3/D.hs, nothing )
+ [1 of 4] Compiling X[sig] ( r3/X.hsig, nothing )
+ [2 of 4] Compiling H[sig] ( r3/H.hsig, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Compiling D ( r3/D.hs, nothing )
diff --git a/testsuite/tests/backpack/should_compile/T13250.stderr b/testsuite/tests/backpack/should_compile/T13250.stderr
index fc79c05623..3f8a6e14eb 100644
--- a/testsuite/tests/backpack/should_compile/T13250.stderr
+++ b/testsuite/tests/backpack/should_compile/T13250.stderr
@@ -8,3 +8,4 @@
[1 of 1] Including p[A=q:A]
Instantiating p[A=q:A]
[1 of 1] Compiling A[sig] ( p/A.hsig, T13250.out/p/p-HVmFlcYSefiK5n1aDP1v7x/A.o )
+ [1 of 1] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/T13323.stderr b/testsuite/tests/backpack/should_compile/T13323.stderr
index 3d6a510ea1..eb49bcbfab 100644
--- a/testsuite/tests/backpack/should_compile/T13323.stderr
+++ b/testsuite/tests/backpack/should_compile/T13323.stderr
@@ -10,4 +10,5 @@
Instantiating p[A=q:A]
[1 of 2] Compiling A[sig] ( p/A.hsig, T13323.out/p/p-HVmFlcYSefiK5n1aDP1v7x/A.o )
[2 of 2] Compiling P ( p/P.hs, T13323.out/p/p-HVmFlcYSefiK5n1aDP1v7x/P.o )
- [1 of 1] Compiling R ( r/R.hs, T13323.out/r/R.o )
+ [1 of 2] Compiling R ( r/R.hs, T13323.out/r/R.o )
+ [2 of 2] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp01.stderr b/testsuite/tests/backpack/should_compile/bkp01.stderr
index 51cc4b7cdd..6b191ebecd 100644
--- a/testsuite/tests/backpack/should_compile/bkp01.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp01.stderr
@@ -2,7 +2,8 @@
[1 of 2] Compiling H[sig] ( p/H.hsig, nothing )
[2 of 2] Compiling A ( p/A.hs, nothing )
[2 of 4] Processing q
- [1 of 1] Compiling H[sig] ( q/H.hsig, nothing )
+ [1 of 2] Compiling H[sig] ( q/H.hsig, nothing )
+ [2 of 2] Instantiating p
[3 of 4] Processing h
Instantiating h
[1 of 1] Compiling H ( h/H.hs, bkp01.out/h/H.o )
@@ -15,4 +16,6 @@
Instantiating p[H=h:H]
[1 of 2] Compiling H[sig] ( p/H.hsig, bkp01.out/p/p-6KeuBvYi0jvLWqVbkSAZMq/H.o )
[2 of 2] Compiling A ( p/A.hs, bkp01.out/p/p-6KeuBvYi0jvLWqVbkSAZMq/A.o )
- [1 of 1] Compiling H[sig] ( q/H.hsig, bkp01.out/q/q-6KeuBvYi0jvLWqVbkSAZMq/H.o )
+ [1 of 2] Compiling H[sig] ( q/H.hsig, bkp01.out/q/q-6KeuBvYi0jvLWqVbkSAZMq/H.o )
+ [2 of 2] Instantiating p
+ [1 of 1] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp02.stderr b/testsuite/tests/backpack/should_compile/bkp02.stderr
index ace97e4b63..cd5cbf9902 100644
--- a/testsuite/tests/backpack/should_compile/bkp02.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp02.stderr
@@ -11,4 +11,5 @@
Instantiating p[H=q:H]
[1 of 2] Compiling H[sig] ( p/H.hsig, bkp02.out/p/p-D5Mg3foBSCrDbQDKH4WGSG/H.o )
[2 of 2] Compiling A ( p/A.hs, bkp02.out/p/p-D5Mg3foBSCrDbQDKH4WGSG/A.o )
- [1 of 1] Compiling R ( r/R.hs, bkp02.out/r/R.o )
+ [1 of 2] Compiling R ( r/R.hs, bkp02.out/r/R.o )
+ [2 of 2] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp07.stderr b/testsuite/tests/backpack/should_compile/bkp07.stderr
index 2ccfaac56a..4ab181e9bd 100644
--- a/testsuite/tests/backpack/should_compile/bkp07.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp07.stderr
@@ -1,5 +1,6 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
- [2 of 2] Compiling B ( q/B.hs, nothing )
+ [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 3] Compiling B ( q/B.hs, nothing )
+ [3 of 3] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp08.stderr b/testsuite/tests/backpack/should_compile/bkp08.stderr
index e81e013bc1..22313331c2 100644
--- a/testsuite/tests/backpack/should_compile/bkp08.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp08.stderr
@@ -9,4 +9,5 @@
[2 of 2] Including r[H=q:H]
Instantiating r[H=q:H]
[1 of 1] Compiling H[sig] ( r/H.hsig, bkp08.out/r/r-D5Mg3foBSCrDbQDKH4WGSG/H.o )
- [1 of 1] Compiling M ( p/M.hs, bkp08.out/p/M.o )
+ [1 of 2] Compiling M ( p/M.hs, bkp08.out/p/M.o )
+ [2 of 2] Instantiating r
diff --git a/testsuite/tests/backpack/should_compile/bkp09.stderr b/testsuite/tests/backpack/should_compile/bkp09.stderr
index 24abba259f..7428ab3eb8 100644
--- a/testsuite/tests/backpack/should_compile/bkp09.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp09.stderr
@@ -6,8 +6,10 @@ bkp09.bkp:1:26: warning:
[2 of 5] Processing q
[1 of 1] Compiling H[sig] ( q/H.hsig, nothing )
[3 of 5] Processing r
- [1 of 2] Compiling H[sig] ( r/H.hsig, nothing )
- [2 of 2] Compiling M ( r/M.hs, nothing )
+ [1 of 4] Compiling H[sig] ( r/H.hsig, nothing )
+ [2 of 4] Compiling M ( r/M.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
[4 of 5] Processing h-impl
Instantiating h-impl
[1 of 1] Compiling H ( h-impl/H.hs, bkp09.out/h-impl/H.o )
@@ -22,5 +24,8 @@ bkp09.bkp:1:26: warning:
[2 of 2] Including q[H=h-impl:H]
Instantiating q[H=h-impl:H]
[1 of 1] Compiling H[sig] ( q/H.hsig, bkp09.out/q/q-5FYQgnNkfSvBT5yogOxPpf/H.o )
- [1 of 2] Compiling H[sig] ( r/H.hsig, bkp09.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
- [2 of 2] Compiling M ( r/M.hs, bkp09.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [1 of 4] Compiling H[sig] ( r/H.hsig, bkp09.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
+ [2 of 4] Compiling M ( r/M.hs, bkp09.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
+ [1 of 1] Instantiating r
diff --git a/testsuite/tests/backpack/should_compile/bkp10.stderr b/testsuite/tests/backpack/should_compile/bkp10.stderr
index 350670e6d4..95f8e632c9 100644
--- a/testsuite/tests/backpack/should_compile/bkp10.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp10.stderr
@@ -2,5 +2,6 @@
[1 of 2] Compiling H[sig] ( p/H.hsig, nothing )
[2 of 2] Compiling A ( p/A.hs, nothing )
[2 of 2] Processing q
- [1 of 2] Compiling H2[sig] ( q/H2.hsig, nothing )
- [2 of 2] Compiling B ( q/B.hs, nothing )
+ [1 of 3] Compiling H2[sig] ( q/H2.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Compiling B ( q/B.hs, nothing )
diff --git a/testsuite/tests/backpack/should_compile/bkp11.stderr b/testsuite/tests/backpack/should_compile/bkp11.stderr
index a804563b2d..e27ed54cec 100644
--- a/testsuite/tests/backpack/should_compile/bkp11.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp11.stderr
@@ -3,5 +3,6 @@
[2 of 3] Compiling H2[sig] ( p/H2.hsig, nothing )
[3 of 3] Compiling A ( p/A.hs, nothing )
[2 of 2] Processing q
- [1 of 2] Compiling H[sig] ( q/H.hsig, nothing )
- [2 of 2] Compiling B ( q/B.hs, nothing )
+ [1 of 3] Compiling H[sig] ( q/H.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Compiling B ( q/B.hs, nothing )
diff --git a/testsuite/tests/backpack/should_compile/bkp12.stderr b/testsuite/tests/backpack/should_compile/bkp12.stderr
index dc4debe3f3..648322e351 100644
--- a/testsuite/tests/backpack/should_compile/bkp12.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp12.stderr
@@ -1,8 +1,9 @@
[1 of 4] Processing p
[1 of 1] Compiling H[sig] ( p/H.hsig, nothing )
[2 of 4] Processing r
- [1 of 2] Compiling H[sig] ( r/H.hsig, nothing )
- [2 of 2] Compiling M ( r/M.hs, nothing )
+ [1 of 3] Compiling H[sig] ( r/H.hsig, nothing )
+ [2 of 3] Compiling M ( r/M.hs, nothing )
+ [3 of 3] Instantiating p
[3 of 4] Processing h-impl
Instantiating h-impl
[1 of 1] Compiling H ( h-impl/H.hs, bkp12.out/h-impl/H.o )
@@ -14,5 +15,7 @@
[1 of 1] Including p[H=h-impl:H]
Instantiating p[H=h-impl:H]
[1 of 1] Compiling H[sig] ( p/H.hsig, bkp12.out/p/p-5FYQgnNkfSvBT5yogOxPpf/H.o )
- [1 of 2] Compiling H[sig] ( r/H.hsig, bkp12.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
- [2 of 2] Compiling M ( r/M.hs, bkp12.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [1 of 3] Compiling H[sig] ( r/H.hsig, bkp12.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
+ [2 of 3] Compiling M ( r/M.hs, bkp12.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [3 of 3] Instantiating p
+ [1 of 1] Instantiating r
diff --git a/testsuite/tests/backpack/should_compile/bkp14.stderr b/testsuite/tests/backpack/should_compile/bkp14.stderr
index b5b40b7eff..fadce50f3e 100644
--- a/testsuite/tests/backpack/should_compile/bkp14.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp14.stderr
@@ -7,5 +7,6 @@
[1 of 2] Compiling F ( impl/F.hs, bkp14.out/impl/F.o )
[2 of 2] Compiling H ( impl/H.hs, bkp14.out/impl/H.o )
[3 of 3] Processing q
- [1 of 2] Compiling Y[sig] ( q/Y.hsig, nothing )
- [2 of 2] Compiling X ( q/X.hs, nothing )
+ [1 of 3] Compiling Y[sig] ( q/Y.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Compiling X ( q/X.hs, nothing )
diff --git a/testsuite/tests/backpack/should_compile/bkp15.stderr b/testsuite/tests/backpack/should_compile/bkp15.stderr
index 904ab2d4cb..d1f29fae2c 100644
--- a/testsuite/tests/backpack/should_compile/bkp15.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp15.stderr
@@ -6,8 +6,10 @@ bkp15.bkp:1:26: warning:
[2 of 5] Processing q
[1 of 1] Compiling H[sig] ( q/H.hsig, nothing )
[3 of 5] Processing r
- [1 of 2] Compiling H[sig] ( r/H.hsig, nothing )
- [2 of 2] Compiling M ( r/M.hs, nothing )
+ [1 of 4] Compiling H[sig] ( r/H.hsig, nothing )
+ [2 of 4] Compiling M ( r/M.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
[4 of 5] Processing h-impl
Instantiating h-impl
[1 of 1] Compiling H ( h-impl/H.hs, bkp15.out/h-impl/H.o )
@@ -21,5 +23,8 @@ bkp15.bkp:1:26: warning:
[2 of 2] Including q[H=h-impl:H]
Instantiating q[H=h-impl:H]
[1 of 1] Compiling H[sig] ( q/H.hsig, bkp15.out/q/q-5FYQgnNkfSvBT5yogOxPpf/H.o )
- [1 of 2] Compiling H[sig] ( r/H.hsig, bkp15.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
- [2 of 2] Compiling M ( r/M.hs, bkp15.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [1 of 4] Compiling H[sig] ( r/H.hsig, bkp15.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
+ [2 of 4] Compiling M ( r/M.hs, bkp15.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
+ [1 of 1] Instantiating r
diff --git a/testsuite/tests/backpack/should_compile/bkp16.stderr b/testsuite/tests/backpack/should_compile/bkp16.stderr
index d09d6e6823..5d105c204b 100644
--- a/testsuite/tests/backpack/should_compile/bkp16.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp16.stderr
@@ -6,3 +6,4 @@
Instantiating p[Int=base-4.13.0.0:GHC.Exts]
[1 of 1] Including ghc-prim-0.8.0
[1 of 1] Compiling Int[sig] ( p/Int.hsig, bkp16.out/p/p-97PZnzqiJmd2hTwUNGdjod/Int.o )
+ [1 of 1] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp17.stderr b/testsuite/tests/backpack/should_compile/bkp17.stderr
index a52394dcaf..151f9e197c 100644
--- a/testsuite/tests/backpack/should_compile/bkp17.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp17.stderr
@@ -8,3 +8,4 @@
[1 of 1] Including p[H=q:M]
Instantiating p[H=q:M]
[1 of 1] Compiling H[sig] ( p/H.hsig, bkp17.out/p/p-Bk81HcBu6NbDb1eswyn055/H.o )
+ [1 of 1] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp18.stderr b/testsuite/tests/backpack/should_compile/bkp18.stderr
index e14b99431c..5fa98e552d 100644
--- a/testsuite/tests/backpack/should_compile/bkp18.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp18.stderr
@@ -11,3 +11,4 @@
Instantiating r[H=h-impl:H]
[1 of 2] Compiling H[sig] ( r/H.hsig, bkp18.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
[2 of 2] Compiling M ( r/M.hs, bkp18.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [1 of 1] Instantiating r
diff --git a/testsuite/tests/backpack/should_compile/bkp19.stderr b/testsuite/tests/backpack/should_compile/bkp19.stderr
index 952fd0ae0c..55e170f32b 100644
--- a/testsuite/tests/backpack/should_compile/bkp19.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp19.stderr
@@ -11,3 +11,4 @@
Instantiating r[H=h-impl:H]
[1 of 2] Compiling H[sig] ( r/H.hsig, bkp19.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
[2 of 2] Compiling M ( r/M.hs, bkp19.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [1 of 1] Instantiating r
diff --git a/testsuite/tests/backpack/should_compile/bkp20.stderr b/testsuite/tests/backpack/should_compile/bkp20.stderr
index 4dfdd7c337..ed2f5bda1a 100644
--- a/testsuite/tests/backpack/should_compile/bkp20.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp20.stderr
@@ -3,8 +3,10 @@
[2 of 5] Processing q
[1 of 1] Compiling H[sig] ( q/H.hsig, nothing )
[3 of 5] Processing r
- [1 of 2] Compiling H[sig] ( r/H.hsig, nothing )
- [2 of 2] Compiling M ( r/M.hs, nothing )
+ [1 of 4] Compiling H[sig] ( r/H.hsig, nothing )
+ [2 of 4] Compiling M ( r/M.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
[4 of 5] Processing h-impl
Instantiating h-impl
[1 of 1] Compiling H ( h-impl/H.hs, bkp20.out/h-impl/H.o )
@@ -18,5 +20,8 @@
[2 of 2] Including q[H=h-impl:H]
Instantiating q[H=h-impl:H]
[1 of 1] Compiling H[sig] ( q/H.hsig, bkp20.out/q/q-5FYQgnNkfSvBT5yogOxPpf/H.o )
- [1 of 2] Compiling H[sig] ( r/H.hsig, bkp20.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
- [2 of 2] Compiling M ( r/M.hs, bkp20.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [1 of 4] Compiling H[sig] ( r/H.hsig, bkp20.out/r/r-5FYQgnNkfSvBT5yogOxPpf/H.o )
+ [2 of 4] Compiling M ( r/M.hs, bkp20.out/r/r-5FYQgnNkfSvBT5yogOxPpf/M.o )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
+ [1 of 1] Instantiating r
diff --git a/testsuite/tests/backpack/should_compile/bkp21.stderr b/testsuite/tests/backpack/should_compile/bkp21.stderr
index abfe9ceffc..35cfa8e3ad 100644
--- a/testsuite/tests/backpack/should_compile/bkp21.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp21.stderr
@@ -3,8 +3,14 @@
[2 of 5] Processing q
[1 of 1] Compiling H[sig] ( q/H.hsig, nothing )
[3 of 5] Processing pq0
- [1 of 1] Compiling H[sig] ( pq0/H.hsig, nothing )
+ [1 of 3] Compiling H[sig] ( pq0/H.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Instantiating q
[4 of 5] Processing pq1
- [1 of 1] Compiling H[sig] ( pq1/H.hsig, nothing )
+ [1 of 3] Compiling H[sig] ( pq1/H.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Instantiating q
[5 of 5] Processing pq2
- [1 of 1] Compiling H[sig] ( pq2/H.hsig, nothing )
+ [1 of 3] Compiling H[sig] ( pq2/H.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp23.stderr b/testsuite/tests/backpack/should_compile/bkp23.stderr
index ea30294f15..18d96656fa 100644
--- a/testsuite/tests/backpack/should_compile/bkp23.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp23.stderr
@@ -3,22 +3,27 @@
[2 of 3] Compiling B[sig] ( p/B.hsig, nothing )
[3 of 3] Compiling M ( p/M.hs, nothing )
[2 of 6] Processing q1
- [1 of 3] Compiling A[sig] ( q1/A.hsig, nothing )
- [2 of 3] Compiling B[sig] ( q1/B.hsig, nothing )
- [3 of 3] Compiling Q ( q1/Q.hs, nothing )
+ [1 of 4] Compiling A[sig] ( q1/A.hsig, nothing )
+ [2 of 4] Compiling B[sig] ( q1/B.hsig, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Compiling Q ( q1/Q.hs, nothing )
[3 of 6] Processing q2
- [1 of 3] Compiling A[sig] ( q2/A.hsig, nothing )
- [2 of 3] Compiling B[sig] ( q2/B.hsig, nothing )
- [3 of 3] Compiling Q ( q2/Q.hs, nothing )
+ [1 of 4] Compiling A[sig] ( q2/A.hsig, nothing )
+ [2 of 4] Compiling B[sig] ( q2/B.hsig, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Compiling Q ( q2/Q.hs, nothing )
[4 of 6] Processing q3
- [1 of 3] Compiling A[sig] ( q3/A.hsig, nothing )
- [2 of 3] Compiling B[sig] ( q3/B.hsig, nothing )
- [3 of 3] Compiling Q ( q3/Q.hs, nothing )
+ [1 of 4] Compiling A[sig] ( q3/A.hsig, nothing )
+ [2 of 4] Compiling B[sig] ( q3/B.hsig, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Compiling Q ( q3/Q.hs, nothing )
[5 of 6] Processing q4
- [1 of 3] Compiling A[sig] ( q4/A.hsig, nothing )
- [2 of 3] Compiling B[sig] ( q4/B.hsig, nothing )
- [3 of 3] Compiling Q ( q4/Q.hs, nothing )
+ [1 of 4] Compiling A[sig] ( q4/A.hsig, nothing )
+ [2 of 4] Compiling B[sig] ( q4/B.hsig, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Compiling Q ( q4/Q.hs, nothing )
[6 of 6] Processing q5
- [1 of 3] Compiling A[sig] ( q5/A.hsig, nothing )
- [2 of 3] Compiling B[sig] ( q5/B.hsig, nothing )
- [3 of 3] Compiling Q ( q5/Q.hs, nothing )
+ [1 of 4] Compiling A[sig] ( q5/A.hsig, nothing )
+ [2 of 4] Compiling B[sig] ( q5/B.hsig, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Compiling Q ( q5/Q.hs, nothing )
diff --git a/testsuite/tests/backpack/should_compile/bkp24.stderr b/testsuite/tests/backpack/should_compile/bkp24.stderr
index ddafe4150b..11c9352b55 100644
--- a/testsuite/tests/backpack/should_compile/bkp24.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp24.stderr
@@ -9,8 +9,9 @@
Instantiating b
[1 of 1] Compiling B ( b/B.hs, bkp24.out/b/B.o )
[4 of 5] Processing q
- [1 of 2] Compiling B[sig] ( q/B.hsig, nothing )
- [2 of 2] Compiling Q ( q/Q.hs, nothing )
+ [1 of 3] Compiling B[sig] ( q/B.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Compiling Q ( q/Q.hs, nothing )
[5 of 5] Processing r
Instantiating r
[1 of 2] Including q[B=b:B]
@@ -21,7 +22,9 @@
[2 of 3] Compiling B[sig] ( p/B.hsig, bkp24.out/p/p-BVwzUlgOVR6H8V9umpUZ2h/B.o )
[3 of 3] Compiling P ( p/P.hs, bkp24.out/p/p-BVwzUlgOVR6H8V9umpUZ2h/P.o )
[2 of 2] Including a
- [1 of 2] Compiling B[sig] ( q/B.hsig, bkp24.out/q/q-3IeW1YRs0cYLmV4oNjoWji/B.o )
- [2 of 2] Compiling Q ( q/Q.hs, bkp24.out/q/q-3IeW1YRs0cYLmV4oNjoWji/Q.o )
+ [1 of 3] Compiling B[sig] ( q/B.hsig, bkp24.out/q/q-3IeW1YRs0cYLmV4oNjoWji/B.o )
+ [2 of 3] Compiling Q ( q/Q.hs, bkp24.out/q/q-3IeW1YRs0cYLmV4oNjoWji/Q.o )
+ [3 of 3] Instantiating p
[2 of 2] Including b
- [1 of 1] Compiling R ( r/R.hs, bkp24.out/r/R.o )
+ [1 of 2] Compiling R ( r/R.hs, bkp24.out/r/R.o )
+ [2 of 2] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp25.stderr b/testsuite/tests/backpack/should_compile/bkp25.stderr
index 55d6e4850a..583577587c 100644
--- a/testsuite/tests/backpack/should_compile/bkp25.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp25.stderr
@@ -6,6 +6,7 @@
Instantiating r
[1 of 1] Compiling Impl ( r/Impl.hs, bkp25.out/r/Impl.o )
[3 of 3] Processing q
- [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
- [2 of 3] Compiling B[sig] ( q/B.hsig, nothing )
- [3 of 3] Compiling M ( q/M.hs, nothing )
+ [1 of 4] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 4] Compiling B[sig] ( q/B.hsig, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Compiling M ( q/M.hs, nothing )
diff --git a/testsuite/tests/backpack/should_compile/bkp26.stderr b/testsuite/tests/backpack/should_compile/bkp26.stderr
index 64960b15c7..1afdcc57bc 100644
--- a/testsuite/tests/backpack/should_compile/bkp26.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp26.stderr
@@ -10,4 +10,5 @@
Instantiating p[A=r:A]
[1 of 2] Compiling A[sig] ( p/A.hsig, bkp26.out/p/p-8YQRY0unRYZCev5HBjXieS/A.o )
[2 of 2] Compiling P ( p/P.hs, bkp26.out/p/p-8YQRY0unRYZCev5HBjXieS/P.o )
- [1 of 1] Compiling M ( q/M.hs, bkp26.out/q/M.o )
+ [1 of 2] Compiling M ( q/M.hs, bkp26.out/q/M.o )
+ [2 of 2] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp27.stderr b/testsuite/tests/backpack/should_compile/bkp27.stderr
index 72722ed2ea..88848886dc 100644
--- a/testsuite/tests/backpack/should_compile/bkp27.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp27.stderr
@@ -11,4 +11,5 @@
[1 of 2] Compiling A[sig] ( p/A.hsig, bkp27.out/p/p-8YQRY0unRYZCev5HBjXieS/A.o )
[2 of 2] Compiling P ( p/P.hs, bkp27.out/p/p-8YQRY0unRYZCev5HBjXieS/P.o )
[2 of 2] Including r
- [1 of 1] Compiling M ( q/M.hs, bkp27.out/q/M.o )
+ [1 of 2] Compiling M ( q/M.hs, bkp27.out/q/M.o )
+ [2 of 2] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp28.stderr b/testsuite/tests/backpack/should_compile/bkp28.stderr
index 9ea43fcb45..6aced9716c 100644
--- a/testsuite/tests/backpack/should_compile/bkp28.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp28.stderr
@@ -4,5 +4,6 @@
[2 of 3] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[3 of 3] Processing q
- [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
- [2 of 2] Compiling B ( q/B.hs, nothing )
+ [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 3] Compiling B ( q/B.hs, nothing )
+ [3 of 3] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp29.stderr b/testsuite/tests/backpack/should_compile/bkp29.stderr
index 1f4652b3a2..9906ca14f5 100644
--- a/testsuite/tests/backpack/should_compile/bkp29.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp29.stderr
@@ -3,5 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling B[sig] ( q/B.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling C[sig] ( r/C.hsig, nothing )
- [2 of 2] Compiling M ( r/M.hs, nothing )
+ [1 of 4] Compiling C[sig] ( r/C.hsig, nothing )
+ [2 of 4] Compiling M ( r/M.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp30.stderr b/testsuite/tests/backpack/should_compile/bkp30.stderr
index 1f4652b3a2..9906ca14f5 100644
--- a/testsuite/tests/backpack/should_compile/bkp30.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp30.stderr
@@ -3,5 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling B[sig] ( q/B.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling C[sig] ( r/C.hsig, nothing )
- [2 of 2] Compiling M ( r/M.hs, nothing )
+ [1 of 4] Compiling C[sig] ( r/C.hsig, nothing )
+ [2 of 4] Compiling M ( r/M.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp31.stderr b/testsuite/tests/backpack/should_compile/bkp31.stderr
index 523a635d3a..dfac74a509 100644
--- a/testsuite/tests/backpack/should_compile/bkp31.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp31.stderr
@@ -2,7 +2,8 @@
[1 of 2] Compiling A[sig] ( ab-sigs/A.hsig, nothing )
[2 of 2] Compiling B[sig] ( ab-sigs/B.hsig, nothing )
[2 of 2] Processing abcd-holes
- [1 of 4] Compiling C ( abcd-holes/C.hs, nothing )
- [2 of 4] Compiling B[sig] ( abcd-holes/B.hsig, nothing )
- [3 of 4] Compiling A[sig] ( abcd-holes/A.hsig, nothing )
- [4 of 4] Compiling D ( abcd-holes/D.hs, nothing )
+ [1 of 5] Compiling C ( abcd-holes/C.hs, nothing )
+ [2 of 5] Compiling B[sig] ( abcd-holes/B.hsig, nothing )
+ [3 of 5] Compiling A[sig] ( abcd-holes/A.hsig, nothing )
+ [4 of 5] Compiling D ( abcd-holes/D.hs, nothing )
+ [5 of 5] Instantiating ab-sigs
diff --git a/testsuite/tests/backpack/should_compile/bkp32.stderr b/testsuite/tests/backpack/should_compile/bkp32.stderr
index c2cea8c2b0..3bdff93eb6 100644
--- a/testsuite/tests/backpack/should_compile/bkp32.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp32.stderr
@@ -1,33 +1,51 @@
[ 1 of 11] Processing prelude-sig
[1 of 1] Compiling Prel[sig] ( prelude-sig/Prel.hsig, nothing )
[ 2 of 11] Processing arrays-sig
- [1 of 2] Compiling Prel[sig] ( arrays-sig/Prel.hsig, nothing )
- [2 of 2] Compiling Array[sig] ( arrays-sig/Array.hsig, nothing )
+ [1 of 3] Compiling Prel[sig] ( arrays-sig/Prel.hsig, nothing )
+ [2 of 3] Compiling Array[sig] ( arrays-sig/Array.hsig, nothing )
+ [3 of 3] Instantiating prelude-sig
[ 3 of 11] Processing structures
- [1 of 5] Compiling Prel[sig] ( structures/Prel.hsig, nothing )
- [2 of 5] Compiling Array[sig] ( structures/Array.hsig, nothing )
- [3 of 5] Compiling Graph ( structures/Graph.hs, nothing )
- [4 of 5] Compiling Tree ( structures/Tree.hs, nothing )
- [5 of 5] Compiling Set ( structures/Set.hs, nothing )
+ [1 of 6] Compiling Prel[sig] ( structures/Prel.hsig, nothing )
+ [2 of 6] Compiling Array[sig] ( structures/Array.hsig, nothing )
+ [3 of 6] Compiling Graph ( structures/Graph.hs, nothing )
+ [4 of 6] Compiling Tree ( structures/Tree.hs, nothing )
+ [5 of 6] Compiling Set ( structures/Set.hs, nothing )
+ [6 of 6] Instantiating arrays-sig
[ 4 of 11] Processing arrays-a
- [1 of 2] Compiling Prel[sig] ( arrays-a/Prel.hsig, nothing )
- [2 of 2] Compiling Array ( arrays-a/Array.hs, nothing )
+ [1 of 3] Compiling Prel[sig] ( arrays-a/Prel.hsig, nothing )
+ [2 of 3] Compiling Array ( arrays-a/Array.hs, nothing )
+ [3 of 3] Instantiating prelude-sig
[ 5 of 11] Processing arrays-b
- [1 of 2] Compiling Prel[sig] ( arrays-b/Prel.hsig, nothing )
- [2 of 2] Compiling Array ( arrays-b/Array.hs, nothing )
+ [1 of 3] Compiling Prel[sig] ( arrays-b/Prel.hsig, nothing )
+ [2 of 3] Compiling Array ( arrays-b/Array.hs, nothing )
+ [3 of 3] Instantiating prelude-sig
[ 6 of 11] Processing graph-a
- [1 of 1] Compiling Prel[sig] ( graph-a/Prel.hsig, nothing )
+ [1 of 3] Compiling Prel[sig] ( graph-a/Prel.hsig, nothing )
+ [2 of 3] Instantiating arrays-a
+ [3 of 3] Instantiating structures
[ 7 of 11] Processing graph-b
- [1 of 1] Compiling Prel[sig] ( graph-b/Prel.hsig, nothing )
+ [1 of 3] Compiling Prel[sig] ( graph-b/Prel.hsig, nothing )
+ [2 of 3] Instantiating arrays-b
+ [3 of 3] Instantiating structures
[ 8 of 11] Processing multiinst
- [1 of 2] Compiling Prel[sig] ( multiinst/Prel.hsig, nothing )
- [2 of 2] Compiling Client ( multiinst/Client.hs, nothing )
+ [1 of 6] Compiling Prel[sig] ( multiinst/Prel.hsig, nothing )
+ [2 of 6] Instantiating arrays-a
+ [3 of 6] Instantiating arrays-b
+ [4 of 6] Instantiating structures
+ [5 of 6] Instantiating structures
+ [6 of 6] Compiling Client ( multiinst/Client.hs, nothing )
[ 9 of 11] Processing applic-left
- [1 of 2] Compiling Prel[sig] ( applic-left/Prel.hsig, nothing )
- [2 of 2] Compiling Left ( applic-left/Left.hs, nothing )
+ [1 of 4] Compiling Prel[sig] ( applic-left/Prel.hsig, nothing )
+ [2 of 4] Instantiating arrays-a
+ [3 of 4] Instantiating structures
+ [4 of 4] Compiling Left ( applic-left/Left.hs, nothing )
[10 of 11] Processing applic-right
- [1 of 2] Compiling Prel[sig] ( applic-right/Prel.hsig, nothing )
- [2 of 2] Compiling Right ( applic-right/Right.hs, nothing )
+ [1 of 4] Compiling Prel[sig] ( applic-right/Prel.hsig, nothing )
+ [2 of 4] Instantiating arrays-a
+ [3 of 4] Instantiating structures
+ [4 of 4] Compiling Right ( applic-right/Right.hs, nothing )
[11 of 11] Processing applic-bot
- [1 of 2] Compiling Prel[sig] ( applic-bot/Prel.hsig, nothing )
- [2 of 2] Compiling Bot ( applic-bot/Bot.hs, nothing )
+ [1 of 4] Compiling Prel[sig] ( applic-bot/Prel.hsig, nothing )
+ [2 of 4] Instantiating applic-left
+ [3 of 4] Instantiating applic-right
+ [4 of 4] Compiling Bot ( applic-bot/Bot.hs, nothing )
diff --git a/testsuite/tests/backpack/should_compile/bkp33.stderr b/testsuite/tests/backpack/should_compile/bkp33.stderr
index 4fa8b755b0..2e88ce8b7f 100644
--- a/testsuite/tests/backpack/should_compile/bkp33.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp33.stderr
@@ -11,4 +11,5 @@
[1 of 2] Compiling A[sig] ( sig/A.hsig, bkp33.out/sig/sig-HyoWTHt34SDIRGEX0vZ8iN/A.o )
[2 of 2] Compiling M ( sig/M.hs, bkp33.out/sig/sig-HyoWTHt34SDIRGEX0vZ8iN/M.o )
[2 of 2] Including mod
- [1 of 1] Compiling S ( join/S.hs, bkp33.out/join/S.o )
+ [1 of 2] Compiling S ( join/S.hs, bkp33.out/join/S.o )
+ [2 of 2] Instantiating sig
diff --git a/testsuite/tests/backpack/should_compile/bkp34.stderr b/testsuite/tests/backpack/should_compile/bkp34.stderr
index 14aa7a843b..44b689db74 100644
--- a/testsuite/tests/backpack/should_compile/bkp34.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp34.stderr
@@ -3,5 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling A[sig] ( r/A.hsig, nothing )
- [2 of 2] Compiling R ( r/R.hs, nothing )
+ [1 of 4] Compiling A[sig] ( r/A.hsig, nothing )
+ [2 of 4] Compiling R ( r/R.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp35.stderr b/testsuite/tests/backpack/should_compile/bkp35.stderr
index 14aa7a843b..44b689db74 100644
--- a/testsuite/tests/backpack/should_compile/bkp35.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp35.stderr
@@ -3,5 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling A[sig] ( r/A.hsig, nothing )
- [2 of 2] Compiling R ( r/R.hs, nothing )
+ [1 of 4] Compiling A[sig] ( r/A.hsig, nothing )
+ [2 of 4] Compiling R ( r/R.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp36.stderr b/testsuite/tests/backpack/should_compile/bkp36.stderr
index 45ade1412f..2538ed6582 100644
--- a/testsuite/tests/backpack/should_compile/bkp36.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp36.stderr
@@ -5,5 +5,6 @@
[1 of 2] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Compiling P ( p/P.hs, nothing )
[3 of 3] Processing q
- [1 of 2] Compiling B[sig] ( q/B.hsig, nothing )
- [2 of 2] Compiling Q ( q/Q.hs, nothing )
+ [1 of 3] Compiling B[sig] ( q/B.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Compiling Q ( q/Q.hs, nothing )
diff --git a/testsuite/tests/backpack/should_compile/bkp37.stderr b/testsuite/tests/backpack/should_compile/bkp37.stderr
index 90438e8c8a..d8bd7a980a 100644
--- a/testsuite/tests/backpack/should_compile/bkp37.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp37.stderr
@@ -8,3 +8,4 @@
[1 of 1] Including p[A=q:A]
Instantiating p[A=q:A]
[1 of 1] Compiling A[sig] ( p/A.hsig, bkp37.out/p/p-HVmFlcYSefiK5n1aDP1v7x/A.o )
+ [1 of 1] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp38.stderr b/testsuite/tests/backpack/should_compile/bkp38.stderr
index bb9ef66c27..7e144fc8ce 100644
--- a/testsuite/tests/backpack/should_compile/bkp38.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp38.stderr
@@ -8,3 +8,4 @@
[1 of 1] Including p[A=q:A]
Instantiating p[A=q:A]
[1 of 1] Compiling A[sig] ( p/A.hsig, bkp38.out/p/p-HVmFlcYSefiK5n1aDP1v7x/A.o )
+ [1 of 1] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp39.stderr b/testsuite/tests/backpack/should_compile/bkp39.stderr
index 924785c9da..a6a991610c 100644
--- a/testsuite/tests/backpack/should_compile/bkp39.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp39.stderr
@@ -10,3 +10,4 @@
Instantiating p[A=q:A]
[1 of 2] Compiling A[sig] ( p/A.hsig, bkp39.out/p/p-HVmFlcYSefiK5n1aDP1v7x/A.o )
[2 of 2] Compiling M ( p/M.hs, bkp39.out/p/p-HVmFlcYSefiK5n1aDP1v7x/M.o )
+ [1 of 1] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp40.stderr b/testsuite/tests/backpack/should_compile/bkp40.stderr
index 00176aabd2..f250951578 100644
--- a/testsuite/tests/backpack/should_compile/bkp40.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp40.stderr
@@ -17,3 +17,5 @@
Instantiating user[Map=eqmap:Map]
[1 of 2] Compiling Map[sig] ( user/Map.hsig, bkp40.out/user/user-9YyTxEeqz3GG5thfDXwuAf/Map.o )
[2 of 2] Compiling User ( user/User.hs, bkp40.out/user/user-9YyTxEeqz3GG5thfDXwuAf/User.o )
+ [1 of 2] Instantiating user
+ [2 of 2] Instantiating user
diff --git a/testsuite/tests/backpack/should_compile/bkp41.stderr b/testsuite/tests/backpack/should_compile/bkp41.stderr
index 0dfe754666..766317718c 100644
--- a/testsuite/tests/backpack/should_compile/bkp41.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp41.stderr
@@ -11,3 +11,4 @@
Instantiating sig[B=impl:B]
[1 of 2] Compiling B[sig] ( sig/B.hsig, bkp41.out/sig/sig-HVnmSw44WZeBfwnUur4wzl/B.o )
[2 of 2] Compiling App ( sig/App.hs, bkp41.out/sig/sig-HVnmSw44WZeBfwnUur4wzl/App.o )
+ [1 of 1] Instantiating sig
diff --git a/testsuite/tests/backpack/should_compile/bkp42.stderr b/testsuite/tests/backpack/should_compile/bkp42.stderr
index 69d8d7cf14..ae2bb75c51 100644
--- a/testsuite/tests/backpack/should_compile/bkp42.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp42.stderr
@@ -12,3 +12,4 @@
Instantiating sig[B=impl:C]
[1 of 2] Compiling B[sig] ( sig/B.hsig, bkp42.out/sig/sig-Ko6MwJiRFc509cOdDShPV5/B.o )
[2 of 2] Compiling App ( sig/App.hs, bkp42.out/sig/sig-Ko6MwJiRFc509cOdDShPV5/App.o )
+ [1 of 1] Instantiating sig
diff --git a/testsuite/tests/backpack/should_compile/bkp43.stderr b/testsuite/tests/backpack/should_compile/bkp43.stderr
index 6915f14f1c..e8beb8c76f 100644
--- a/testsuite/tests/backpack/should_compile/bkp43.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp43.stderr
@@ -1,8 +1,9 @@
[1 of 4] Processing sig
[1 of 1] Compiling A[sig] ( sig/A.hsig, nothing )
[2 of 4] Processing blub
- [1 of 2] Compiling A[sig] ( blub/A.hsig, nothing )
- [2 of 2] Compiling M ( blub/M.hs, nothing )
+ [1 of 3] Compiling A[sig] ( blub/A.hsig, nothing )
+ [2 of 3] Compiling M ( blub/M.hs, nothing )
+ [3 of 3] Instantiating sig
[3 of 4] Processing impl
Instantiating impl
[1 of 1] Compiling A ( impl/A.hs, bkp43.out/impl/A.o )
@@ -12,3 +13,4 @@
Instantiating blub[A=impl:A]
[1 of 2] Compiling A[sig] ( blub/A.hsig, bkp43.out/blub/blub-EMBMWyCjWt1EWXmIjSqmRG/A.o )
[2 of 2] Compiling M ( blub/M.hs, bkp43.out/blub/blub-EMBMWyCjWt1EWXmIjSqmRG/M.o )
+ [1 of 1] Instantiating blub
diff --git a/testsuite/tests/backpack/should_compile/bkp44.stderr b/testsuite/tests/backpack/should_compile/bkp44.stderr
index 020dfa67ca..83a8578dcd 100644
--- a/testsuite/tests/backpack/should_compile/bkp44.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp44.stderr
@@ -2,9 +2,10 @@
[1 of 2] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Compiling B[sig] ( p/B.hsig, nothing )
[2 of 4] Processing q
- [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
- [2 of 3] Compiling B[sig] ( q/B.hsig, nothing )
- [3 of 3] Compiling M ( q/M.hs, nothing )
+ [1 of 4] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 4] Compiling B[sig] ( q/B.hsig, nothing )
+ [3 of 4] Compiling M ( q/M.hs, nothing )
+ [4 of 4] Instantiating p
[3 of 4] Processing pimpl
Instantiating pimpl
[1 of 2] Compiling A ( pimpl/A.hs, bkp44.out/pimpl/A.o )
@@ -16,3 +17,4 @@
[1 of 3] Compiling A[sig] ( q/A.hsig, bkp44.out/q/q-BxPafal3NcFHV8AOBzU3fg/A.o )
[2 of 3] Compiling B[sig] ( q/B.hsig, bkp44.out/q/q-BxPafal3NcFHV8AOBzU3fg/B.o )
[3 of 3] Compiling M ( q/M.hs, bkp44.out/q/q-BxPafal3NcFHV8AOBzU3fg/M.o )
+ [1 of 1] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp45.stderr b/testsuite/tests/backpack/should_compile/bkp45.stderr
index 4a6f1d68aa..aaefe2a527 100644
--- a/testsuite/tests/backpack/should_compile/bkp45.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp45.stderr
@@ -3,5 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling A[sig] ( r/A.hsig, nothing )
- [2 of 2] Compiling B ( r/B.hs, nothing )
+ [1 of 4] Compiling A[sig] ( r/A.hsig, nothing )
+ [2 of 4] Compiling B ( r/B.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp46.stderr b/testsuite/tests/backpack/should_compile/bkp46.stderr
index 220eb96ab3..5706fd457d 100644
--- a/testsuite/tests/backpack/should_compile/bkp46.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp46.stderr
@@ -10,3 +10,4 @@
Instantiating p[A=i:A]
[1 of 2] Compiling A[sig] ( p/A.hsig, bkp46.out/p/p-CtJxD03mJqIIVJzOga8l4X/A.o )
[2 of 2] Compiling B ( p/B.hs, bkp46.out/p/p-CtJxD03mJqIIVJzOga8l4X/B.o )
+ [1 of 1] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp47.stderr b/testsuite/tests/backpack/should_compile/bkp47.stderr
index 0cc25d58c1..134cbd4f42 100644
--- a/testsuite/tests/backpack/should_compile/bkp47.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp47.stderr
@@ -3,10 +3,12 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling A[sig] ( r/A.hsig, nothing )
- [2 of 2] Compiling B ( r/B.hs, nothing )
+ [1 of 4] Compiling A[sig] ( r/A.hsig, nothing )
+ [2 of 4] Compiling B ( r/B.hs, nothing )
bkp47.bkp:19:18: warning: [-Wmissing-methods (in -Wdefault)]
• No explicit implementation for
either ‘f’ or ‘g’
• In the instance declaration for ‘C Int’
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp48.stderr b/testsuite/tests/backpack/should_compile/bkp48.stderr
index ae6c7fc575..e1d0213493 100644
--- a/testsuite/tests/backpack/should_compile/bkp48.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp48.stderr
@@ -3,7 +3,9 @@
[2 of 5] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 5] Processing r
- [1 of 1] Compiling A[sig] ( r/A.hsig, nothing )
+ [1 of 3] Compiling A[sig] ( r/A.hsig, nothing )
+ [2 of 3] Instantiating p
+ [3 of 3] Instantiating q
[4 of 5] Processing i
Instantiating i
[1 of 1] Compiling A ( i/A.hs, bkp48.out/i/A.o )
@@ -17,6 +19,11 @@
[2 of 2] Including q[A=i:A]
Instantiating q[A=i:A]
[1 of 1] Compiling A[sig] ( q/A.hsig, bkp48.out/q/q-CtJxD03mJqIIVJzOga8l4X/A.o )
- [1 of 1] Compiling A[sig] ( r/A.hsig, bkp48.out/r/r-CtJxD03mJqIIVJzOga8l4X/A.o )
+ [1 of 3] Compiling A[sig] ( r/A.hsig, bkp48.out/r/r-CtJxD03mJqIIVJzOga8l4X/A.o )
+ [2 of 3] Instantiating p
+ [3 of 3] Instantiating q
[2 of 3] Including p[A=i:A]
[3 of 3] Including q[A=i:A]
+ [1 of 3] Instantiating r
+ [2 of 3] Instantiating p
+ [3 of 3] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp49.stderr b/testsuite/tests/backpack/should_compile/bkp49.stderr
index d8f64f0657..e18512573b 100644
--- a/testsuite/tests/backpack/should_compile/bkp49.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp49.stderr
@@ -1,4 +1,5 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
+ [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 2] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp50.stderr b/testsuite/tests/backpack/should_compile/bkp50.stderr
index d8f64f0657..e18512573b 100644
--- a/testsuite/tests/backpack/should_compile/bkp50.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp50.stderr
@@ -1,4 +1,5 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
+ [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 2] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp51.stderr b/testsuite/tests/backpack/should_compile/bkp51.stderr
index 652f309735..9ce49d116b 100644
--- a/testsuite/tests/backpack/should_compile/bkp51.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp51.stderr
@@ -8,15 +8,20 @@
[2 of 3] Compiling H[sig] ( q/H.hsig, nothing )
[3 of 3] Compiling C ( q/C.hs, nothing )
[3 of 6] Processing r
- [1 of 3] Compiling H[sig] ( r/H.hsig, nothing )
- [2 of 3] Compiling B[sig] ( r/B.hsig, nothing )
- [3 of 3] Compiling D ( r/D.hs, nothing )
+ [1 of 4] Compiling H[sig] ( r/H.hsig, nothing )
+ [2 of 4] Compiling B[sig] ( r/B.hsig, nothing )
+ [3 of 4] Compiling D ( r/D.hs, nothing )
+ [4 of 4] Instantiating q
[4 of 6] Processing s
- [1 of 2] Compiling H[sig] ( s/H.hsig, nothing )
- [2 of 2] Compiling E ( s/E.hs, nothing )
+ [1 of 3] Compiling H[sig] ( s/H.hsig, nothing )
+ [2 of 3] Instantiating r
+ [3 of 3] Compiling E ( s/E.hs, nothing )
[5 of 6] Processing t
- [1 of 2] Compiling H[sig] ( t/H.hsig, nothing )
- [2 of 2] Compiling F ( t/F.hs, nothing )
+ [1 of 4] Compiling H[sig] ( t/H.hsig, nothing )
+ [2 of 4] Instantiating s
+ [3 of 4] Instantiating r
+ [4 of 4] Compiling F ( t/F.hs, nothing )
[6 of 6] Processing u
- [1 of 2] Compiling H[sig] ( u/H.hsig, nothing )
- [2 of 2] Compiling G ( u/G.hs, nothing )
+ [1 of 3] Compiling H[sig] ( u/H.hsig, nothing )
+ [2 of 3] Instantiating q
+ [3 of 3] Compiling G ( u/G.hs, nothing )
diff --git a/testsuite/tests/backpack/should_compile/bkp53.stderr b/testsuite/tests/backpack/should_compile/bkp53.stderr
index a2b19452b2..ccf948619f 100644
--- a/testsuite/tests/backpack/should_compile/bkp53.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp53.stderr
@@ -3,5 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling A[sig] ( r/A.hsig, nothing )
- [2 of 2] Compiling M ( r/M.hs, nothing )
+ [1 of 4] Compiling A[sig] ( r/A.hsig, nothing )
+ [2 of 4] Compiling M ( r/M.hs, nothing )
+ [3 of 4] Instantiating p
+ [4 of 4] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp54.stderr b/testsuite/tests/backpack/should_compile/bkp54.stderr
index f3aafc1258..75815bb8b6 100644
--- a/testsuite/tests/backpack/should_compile/bkp54.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp54.stderr
@@ -1,5 +1,6 @@
[1 of 2] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[2 of 2] Processing p
- [1 of 2] Compiling A[sig] ( p/A.hsig, nothing )
- [2 of 2] Compiling M ( p/M.hs, nothing )
+ [1 of 3] Compiling A[sig] ( p/A.hsig, nothing )
+ [2 of 3] Compiling M ( p/M.hs, nothing )
+ [3 of 3] Instantiating q
diff --git a/testsuite/tests/backpack/should_compile/bkp55.stderr b/testsuite/tests/backpack/should_compile/bkp55.stderr
index 9213c9c84f..5c55e4e992 100644
--- a/testsuite/tests/backpack/should_compile/bkp55.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp55.stderr
@@ -1,5 +1,6 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 2] Compiling B[sig] ( q/B.hsig, nothing )
- [2 of 2] Compiling M ( q/M.hs, nothing )
+ [1 of 3] Compiling B[sig] ( q/B.hsig, nothing )
+ [2 of 3] Compiling M ( q/M.hs, nothing )
+ [3 of 3] Instantiating p
diff --git a/testsuite/tests/backpack/should_compile/bkp57.stderr b/testsuite/tests/backpack/should_compile/bkp57.stderr
index 96f769a402..dc2eeb19cc 100644
--- a/testsuite/tests/backpack/should_compile/bkp57.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp57.stderr
@@ -16,4 +16,5 @@
[1 of 1] Including common
[1 of 2] Compiling Instance[sig] ( consumer-abs/Instance.hsig, bkp57.out/consumer-abs/consumer-abs-EtqPCpl4Hcf9otzJUe9fPM/Instance.o )
[2 of 2] Compiling Downstream ( consumer-abs/Downstream.hs, bkp57.out/consumer-abs/consumer-abs-EtqPCpl4Hcf9otzJUe9fPM/Downstream.o )
- [1 of 1] Compiling Tie ( tie/Tie.hs, bkp57.out/tie/Tie.o )
+ [1 of 2] Compiling Tie ( tie/Tie.hs, bkp57.out/tie/Tie.o )
+ [2 of 2] Instantiating consumer-abs
diff --git a/testsuite/tests/backpack/should_compile/bkp59.stderr b/testsuite/tests/backpack/should_compile/bkp59.stderr
index 364d6c2601..6938021c4a 100644
--- a/testsuite/tests/backpack/should_compile/bkp59.stderr
+++ b/testsuite/tests/backpack/should_compile/bkp59.stderr
@@ -16,4 +16,5 @@
[1 of 1] Including common
[1 of 2] Compiling Instance[sig] ( consumer-abs/Instance.hsig, bkp59.out/consumer-abs/consumer-abs-EtqPCpl4Hcf9otzJUe9fPM/Instance.o )
[2 of 2] Compiling Downstream ( consumer-abs/Downstream.hs, bkp59.out/consumer-abs/consumer-abs-EtqPCpl4Hcf9otzJUe9fPM/Downstream.o )
- [1 of 1] Compiling Tie ( tie/Tie.hs, bkp59.out/tie/Tie.o )
+ [1 of 2] Compiling Tie ( tie/Tie.hs, bkp59.out/tie/Tie.o )
+ [2 of 2] Instantiating consumer-abs
diff --git a/testsuite/tests/backpack/should_fail/all.T b/testsuite/tests/backpack/should_fail/all.T
index b9d1eeba3e..5e0d6fdeea 100644
--- a/testsuite/tests/backpack/should_fail/all.T
+++ b/testsuite/tests/backpack/should_fail/all.T
@@ -45,3 +45,7 @@ test('bkpfail46', normal, backpack_compile_fail, [''])
test('bkpfail47', normal, backpack_compile_fail, [''])
test('bkpfail48', normal, backpack_compile_fail, [''])
test('bkpfail49', normal, backpack_compile_fail, [''])
+test('bkpfail50', normal, backpack_compile_fail, [''])
+test('bkpfail51', normal, backpack_compile_fail, [''])
+test('bkpfail52', normal, backpack_compile_fail, [''])
+test('bkpfail53', normal, backpack_compile_fail, [''])
diff --git a/testsuite/tests/backpack/should_fail/bkpfail04.stderr b/testsuite/tests/backpack/should_fail/bkpfail04.stderr
index 0cb8d9cfe0..397cd24851 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail04.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail04.stderr
@@ -3,7 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling A[sig] ( r/A.hsig, nothing )
+ [1 of 4] Compiling A[sig] ( r/A.hsig, nothing )
bkpfail04.bkp:7:9: error:
• Type constructor ‘A’ has conflicting definitions in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail05.stderr b/testsuite/tests/backpack/should_fail/bkpfail05.stderr
index b231bbdb5b..da996cfb7e 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail05.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail05.stderr
@@ -4,7 +4,8 @@
Instantiating t-impl
[1 of 1] Compiling T ( t-impl/T.hs, bkpfail05.out/t-impl/T.o )
[3 of 5] Processing p
- [1 of 1] Compiling H[sig] ( p/H.hsig, nothing )
+ [1 of 2] Compiling H[sig] ( p/H.hsig, nothing )
+ [2 of 2] Instantiating h
[4 of 5] Processing h-impl
Instantiating h-impl
[1 of 1] Including t-impl
diff --git a/testsuite/tests/backpack/should_fail/bkpfail07.stderr b/testsuite/tests/backpack/should_fail/bkpfail07.stderr
index 05277035dd..251fd67f0b 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail07.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail07.stderr
@@ -5,7 +5,9 @@
[2 of 3] Compiling H ( h/H.hs, nothing )
[3 of 3] Compiling A[sig] ( h/A.hsig, nothing )
[3 of 3] Processing q
- [1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
+ [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 3] Instantiating h
+ [3 of 3] Instantiating p
bkpfail07.bkp:6:9: error:
• Type constructor ‘T’ has conflicting definitions in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail09.stderr b/testsuite/tests/backpack/should_fail/bkpfail09.stderr
index b33c3b4b77..de1d100a34 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail09.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail09.stderr
@@ -5,6 +5,8 @@
Instantiating q
[1 of 1] Compiling H ( q/H.hs, bkpfail09.out/q/H.o )
[3 of 3] Processing r
+ [1 of 3] Compiling H2[sig] ( r/H2.hsig, nothing )
+ [2 of 3] Instantiating p
Command line argument: -unit-id p[H=H]:0:0: error:
• ‘H’ is exported by the hsig file, but not exported by the implementing module ‘q:H’
diff --git a/testsuite/tests/backpack/should_fail/bkpfail12.stderr b/testsuite/tests/backpack/should_fail/bkpfail12.stderr
index 0526da438c..f240d2f058 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail12.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail12.stderr
@@ -5,6 +5,8 @@
Instantiating q
[1 of 1] Compiling Q ( q/Q.hs, bkpfail12.out/q/Q.o )
[3 of 3] Processing r
+ [1 of 3] Compiling H[sig] ( r/H.hsig, nothing )
+ [2 of 3] Instantiating p
bkpfail12.bkp:8:9: error:
• Identifier ‘f’ has conflicting definitions in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail13.stderr b/testsuite/tests/backpack/should_fail/bkpfail13.stderr
index afd4474f35..13d227a617 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail13.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail13.stderr
@@ -5,6 +5,8 @@
Instantiating q
[1 of 1] Compiling QMe ( q/QMe.hs, bkpfail13.out/q/QMe.o )
[3 of 3] Processing r
+ [1 of 3] Compiling H[sig] ( r/H.hsig, nothing )
+ [2 of 3] Instantiating p
bkpfail13.bkp:8:9: error:
• Identifier ‘f’ has conflicting definitions in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail14.stderr b/testsuite/tests/backpack/should_fail/bkpfail14.stderr
index d89e6cab28..401cab2286 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail14.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail14.stderr
@@ -8,6 +8,8 @@
[2 of 3] Compiling Q ( q/Q.hs, bkpfail14.out/q/Q.o )
[3 of 3] Compiling Q2 ( q/Q2.hs, bkpfail14.out/q/Q2.o )
[3 of 3] Processing r
+ [1 of 3] Compiling H[sig] ( r/H.hsig, nothing )
+ [2 of 3] Instantiating p
bkpfail14.bkp:9:9: error:
• Identifier ‘f’ has conflicting definitions in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail15.stderr b/testsuite/tests/backpack/should_fail/bkpfail15.stderr
index f32cd6dcf7..cf30efe6f8 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail15.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail15.stderr
@@ -6,7 +6,8 @@
Instantiating q
[1 of 1] Compiling Q ( q/Q.hs, bkpfail15.out/q/Q.o )
[3 of 3] Processing r
- [1 of 1] Compiling A[sig] ( r/A.hsig, nothing )
+ [1 of 2] Compiling A[sig] ( r/A.hsig, nothing )
+ [2 of 2] Instantiating p
bkpfail15.bkp:8:9: error:
• Identifier ‘f’ has conflicting definitions in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail20.stderr b/testsuite/tests/backpack/should_fail/bkpfail20.stderr
index 4e95695a15..bd450f9f8c 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail20.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail20.stderr
@@ -3,7 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 1] Compiling B[sig] ( r/B.hsig, nothing )
+ [1 of 3] Compiling B[sig] ( r/B.hsig, nothing )
bkpfail20.bkp:1:1: error:
• While merging export lists, could not unify Data.STRef.Lazy.newSTRef with GHC.STRef.newSTRef
diff --git a/testsuite/tests/backpack/should_fail/bkpfail21.stderr b/testsuite/tests/backpack/should_fail/bkpfail21.stderr
index 693135bd45..bc40bbc344 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail21.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail21.stderr
@@ -5,9 +5,9 @@
[1 of 2] Compiling B[sig] ( q/B.hsig, nothing )
[2 of 2] Compiling C[sig] ( q/C.hsig, nothing )
[3 of 3] Processing r
- [1 of 3] Compiling H2[sig] ( r/H2.hsig, nothing )
- [2 of 3] Compiling H1[sig] ( r/H1.hsig, nothing )
- [3 of 3] Compiling H3[sig] ( r/H3.hsig, nothing )
+ [1 of 5] Compiling H2[sig] ( r/H2.hsig, nothing )
+ [2 of 5] Compiling H1[sig] ( r/H1.hsig, nothing )
+ [3 of 5] Compiling H3[sig] ( r/H3.hsig, nothing )
bkpfail21.bkp:1:1: error:
• While merging export lists, could not unify {H1.T} with {H2.T}
diff --git a/testsuite/tests/backpack/should_fail/bkpfail28.stderr b/testsuite/tests/backpack/should_fail/bkpfail28.stderr
index 4428da9a41..4850e19240 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail28.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail28.stderr
@@ -3,8 +3,8 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling A[sig] ( r/A.hsig, nothing )
- [2 of 2] Compiling R ( r/R.hs, nothing )
+ [1 of 4] Compiling A[sig] ( r/A.hsig, nothing )
+ [2 of 4] Compiling R ( r/R.hs, nothing )
bkpfail28.bkp:18:13: error:
• Overlapping instances for Show (K a) arising from a use of ‘show’
diff --git a/testsuite/tests/backpack/should_fail/bkpfail29.stderr b/testsuite/tests/backpack/should_fail/bkpfail29.stderr
index dde8978471..dc4f64768a 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail29.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail29.stderr
@@ -3,7 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 2] Compiling A[sig] ( r/A.hsig, nothing )
+ [1 of 4] Compiling A[sig] ( r/A.hsig, nothing )
bkpfail29.bkp:8:9: error:
• Cycle in type synonym declarations:
diff --git a/testsuite/tests/backpack/should_fail/bkpfail31.stderr b/testsuite/tests/backpack/should_fail/bkpfail31.stderr
index b5c9bc7b1f..ab599229ad 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail31.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail31.stderr
@@ -1,7 +1,7 @@
[1 of 4] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 4] Processing q
- [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
+ [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
<no location info>: error:
The identifier T does not exist in the local signature.
diff --git a/testsuite/tests/backpack/should_fail/bkpfail33.stderr b/testsuite/tests/backpack/should_fail/bkpfail33.stderr
index 4da8897b68..addc8d9733 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail33.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail33.stderr
@@ -1,7 +1,7 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
+ [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
bkpfail33.bkp:5:18: error:
• Not in scope: type constructor or class ‘T’
diff --git a/testsuite/tests/backpack/should_fail/bkpfail34.stderr b/testsuite/tests/backpack/should_fail/bkpfail34.stderr
index 225e491406..cbe8a1bdbe 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail34.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail34.stderr
@@ -1,7 +1,7 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
+ [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
<no location info>: error:
The identifier T does not exist in the local signature.
diff --git a/testsuite/tests/backpack/should_fail/bkpfail35.stderr b/testsuite/tests/backpack/should_fail/bkpfail35.stderr
index cbb2152f7f..893a8dd2ae 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail35.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail35.stderr
@@ -2,7 +2,8 @@
[1 of 2] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Compiling B ( p/B.hs, nothing )
[2 of 4] Processing q
- [1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
+ [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 2] Instantiating p
[3 of 4] Processing aimpl
Instantiating aimpl
[1 of 1] Compiling A ( aimpl/A.hs, bkpfail35.out/aimpl/A.o )
diff --git a/testsuite/tests/backpack/should_fail/bkpfail36.stderr b/testsuite/tests/backpack/should_fail/bkpfail36.stderr
index cd65f67384..e031625aac 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail36.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail36.stderr
@@ -2,8 +2,8 @@
[1 of 2] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Compiling B[sig] ( p/B.hsig, nothing )
[2 of 2] Processing q
- [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
- [2 of 2] Compiling B[sig] ( q/B.hsig, nothing )
+ [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 3] Compiling B[sig] ( q/B.hsig, nothing )
<no location info>: error:
The identifier T does not exist in the signature for <A>
diff --git a/testsuite/tests/backpack/should_fail/bkpfail38.stderr b/testsuite/tests/backpack/should_fail/bkpfail38.stderr
index df4a1d0483..264e150783 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail38.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail38.stderr
@@ -3,7 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 1] Compiling A[sig] ( r/A.hsig, nothing )
+ [1 of 3] Compiling A[sig] ( r/A.hsig, nothing )
bkpfail38.bkp:8:9: error:
• Identifier ‘op’ has conflicting fixities in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail41.stderr b/testsuite/tests/backpack/should_fail/bkpfail41.stderr
index 6cd72dcad1..6f58345fe7 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail41.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail41.stderr
@@ -5,7 +5,8 @@
Instantiating i
[1 of 1] Compiling A ( i/A.hs, bkpfail41.out/i/A.o )
[3 of 3] Processing r
- [1 of 1] Compiling B[sig] ( r/B.hsig, nothing )
+ [1 of 2] Compiling B[sig] ( r/B.hsig, nothing )
+ [2 of 2] Instantiating p
bkpfail41.bkp:10:9: error:
• Class ‘C’ has conflicting definitions in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail42.stderr b/testsuite/tests/backpack/should_fail/bkpfail42.stderr
index 5b078910f9..aa6857e9a1 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail42.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail42.stderr
@@ -1,7 +1,7 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
+ [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
bkpfail42.bkp:9:9: error:
• Type constructor ‘F’ has conflicting definitions in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail47.stderr b/testsuite/tests/backpack/should_fail/bkpfail47.stderr
index 0eb58d8ee4..d7f7c174d6 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail47.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail47.stderr
@@ -3,7 +3,7 @@
[2 of 3] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[3 of 3] Processing r
- [1 of 1] Compiling A[sig] ( r/A.hsig, nothing )
+ [1 of 3] Compiling A[sig] ( r/A.hsig, nothing )
bkpfail47.bkp:9:9: error:
• Type constructor ‘T’ has conflicting definitions in the module
diff --git a/testsuite/tests/backpack/should_fail/bkpfail48.stderr b/testsuite/tests/backpack/should_fail/bkpfail48.stderr
index cb0740d8bf..27a1f25ac0 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail48.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail48.stderr
@@ -1,7 +1,7 @@
[1 of 2] Processing q
[1 of 1] Compiling A[sig] ( q/A.hsig, nothing )
[2 of 2] Processing p
- [1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
+ [1 of 2] Compiling A[sig] ( p/A.hsig, nothing )
bkpfail48.bkp:6:18: error:
• The export item ‘module Data.Bool’ is not imported
diff --git a/testsuite/tests/backpack/should_fail/bkpfail49.stderr b/testsuite/tests/backpack/should_fail/bkpfail49.stderr
index c2236e5375..27892ec8cf 100644
--- a/testsuite/tests/backpack/should_fail/bkpfail49.stderr
+++ b/testsuite/tests/backpack/should_fail/bkpfail49.stderr
@@ -1,8 +1,8 @@
[1 of 2] Processing p
[1 of 1] Compiling A[sig] ( p/A.hsig, nothing )
[2 of 2] Processing q
- [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
- [2 of 2] Compiling M ( q/M.hs, nothing )
+ [1 of 3] Compiling A[sig] ( q/A.hsig, nothing )
+ [2 of 3] Compiling M ( q/M.hs, nothing )
bkpfail49.bkp:11:13: error:
Not in scope: data constructor ‘A.True’
diff --git a/testsuite/tests/backpack/should_fail/bkpfail50.bkp b/testsuite/tests/backpack/should_fail/bkpfail50.bkp
new file mode 100644
index 0000000000..1dda1cb119
--- /dev/null
+++ b/testsuite/tests/backpack/should_fail/bkpfail50.bkp
@@ -0,0 +1,8 @@
+unit p where
+ signature H where
+ data T = T Int
+unit q where
+ dependency p[H=<A>]
+ signature A where
+ data T = T Bool
+-- signatures don't merge
diff --git a/testsuite/tests/backpack/should_fail/bkpfail50.stderr b/testsuite/tests/backpack/should_fail/bkpfail50.stderr
new file mode 100644
index 0000000000..2d4d171ea7
--- /dev/null
+++ b/testsuite/tests/backpack/should_fail/bkpfail50.stderr
@@ -0,0 +1,16 @@
+[1 of 2] Processing p
+ [1 of 1] Compiling H[sig] ( p/H.hsig, nothing )
+[2 of 2] Processing q
+ [1 of 2] Compiling A[sig] ( q/A.hsig, nothing )
+
+bkpfail50.bkp:7:9: error:
+ • Type constructor ‘T’ has conflicting definitions in the module
+ and its hsig file
+ Main module: type T :: *
+ data T = T Bool
+ Hsig file: type T :: *
+ data T = T Int
+ The constructors do not match: The types for ‘T’ differ
+ • while merging the signatures from:
+ • p[H=<A>]:H
+ • ...and the local signature for A
diff --git a/testsuite/tests/backpack/should_fail/bkpfail51.bkp b/testsuite/tests/backpack/should_fail/bkpfail51.bkp
new file mode 100644
index 0000000000..e8cfe5938d
--- /dev/null
+++ b/testsuite/tests/backpack/should_fail/bkpfail51.bkp
@@ -0,0 +1,11 @@
+unit p where
+ signature H where
+ data T = T Int
+ module I(module H) where
+ import H
+unit q where
+ dependency p[H=<A>]
+ signature A where
+ import I
+ type T = H.T
+-- cyclic import
diff --git a/testsuite/tests/backpack/should_fail/bkpfail51.stderr b/testsuite/tests/backpack/should_fail/bkpfail51.stderr
new file mode 100644
index 0000000000..c732e0bcbf
--- /dev/null
+++ b/testsuite/tests/backpack/should_fail/bkpfail51.stderr
@@ -0,0 +1,8 @@
+[1 of 2] Processing p
+ [1 of 2] Compiling H[sig] ( p/H.hsig, nothing )
+ [2 of 2] Compiling I ( p/I.hs, nothing )
+[2 of 2] Processing q
+Module imports and instantiations form a cycle:
+ instantiated unit p[H=A]
+ imports module ‘A’ (q/A.hsig)
+ which imports instantiated unit p[H=A]
diff --git a/testsuite/tests/backpack/should_fail/bkpfail52.bkp b/testsuite/tests/backpack/should_fail/bkpfail52.bkp
new file mode 100644
index 0000000000..da5a3c0822
--- /dev/null
+++ b/testsuite/tests/backpack/should_fail/bkpfail52.bkp
@@ -0,0 +1,11 @@
+unit p where
+ signature H where
+ data T = T Int
+unit q where
+ dependency p[H=<A>]
+ module B where
+ data T = T Bool
+ signature A where
+ import qualified B
+ type T = B.T
+-- signatures don't merge
diff --git a/testsuite/tests/backpack/should_fail/bkpfail52.stderr b/testsuite/tests/backpack/should_fail/bkpfail52.stderr
new file mode 100644
index 0000000000..888434e33c
--- /dev/null
+++ b/testsuite/tests/backpack/should_fail/bkpfail52.stderr
@@ -0,0 +1,16 @@
+[1 of 2] Processing p
+ [1 of 1] Compiling H[sig] ( p/H.hsig, nothing )
+[2 of 2] Processing q
+ [1 of 3] Compiling B ( q/B.hs, nothing )
+ [2 of 3] Compiling A[sig] ( q/A.hsig, nothing )
+
+bkpfail52.bkp:10:9: error:
+ • Type constructor ‘T’ has conflicting definitions in the module
+ and its hsig file
+ Main module: type T :: *
+ type T = B.T
+ Hsig file: type T :: *
+ data T = T Int
+ • while merging the signatures from:
+ • p[H=<A>]:H
+ • ...and the local signature for A
diff --git a/testsuite/tests/backpack/should_fail/bkpfail53.bkp b/testsuite/tests/backpack/should_fail/bkpfail53.bkp
new file mode 100644
index 0000000000..47e7c4593c
--- /dev/null
+++ b/testsuite/tests/backpack/should_fail/bkpfail53.bkp
@@ -0,0 +1,21 @@
+
+unit p where
+ signature H where
+ data T = T Int
+ module I(module H) where
+ import H
+ x :: Int -> T
+ x = T
+unit q where
+ dependency p[H=<A>]
+ module B where
+ data T = T Bool
+ signature A where
+ import qualified B
+ type T = B.T
+ module C where
+ import qualified B
+ import qualified I
+ x :: Int -> B.T
+ x = I.x
+-- signatures don't merge
diff --git a/testsuite/tests/backpack/should_fail/bkpfail53.stderr b/testsuite/tests/backpack/should_fail/bkpfail53.stderr
new file mode 100644
index 0000000000..b694bc57ff
--- /dev/null
+++ b/testsuite/tests/backpack/should_fail/bkpfail53.stderr
@@ -0,0 +1,17 @@
+[1 of 2] Processing p
+ [1 of 2] Compiling H[sig] ( p/H.hsig, nothing )
+ [2 of 2] Compiling I ( p/I.hs, nothing )
+[2 of 2] Processing q
+ [1 of 4] Compiling B ( q/B.hs, nothing )
+ [2 of 4] Compiling A[sig] ( q/A.hsig, nothing )
+
+bkpfail53.bkp:15:9: error:
+ • Type constructor ‘T’ has conflicting definitions in the module
+ and its hsig file
+ Main module: type T :: *
+ type T = B.T
+ Hsig file: type T :: *
+ data T = T Int
+ • while merging the signatures from:
+ • p[H=<A>]:H
+ • ...and the local signature for A
diff --git a/testsuite/tests/ghc-api/downsweep/OldModLocation.hs b/testsuite/tests/ghc-api/downsweep/OldModLocation.hs
index 76338b0f1e..180932bd18 100644
--- a/testsuite/tests/ghc-api/downsweep/OldModLocation.hs
+++ b/testsuite/tests/ghc-api/downsweep/OldModLocation.hs
@@ -3,6 +3,7 @@
import GHC
import GHC.Driver.Make
import GHC.Driver.Session
+import GHC.Unit.Module.ModSummary (ExtendedModSummary(..))
import GHC.Unit.Finder
import Control.Monad.IO.Class (liftIO)
@@ -54,7 +55,7 @@ main = do
-- using the 'location' parameter we'd end up using the old location of
-- the "B" module in this test. Make sure that doesn't happen.
- hPrint stderr $ sort (map (ml_hs_file . ms_location) (rights emss))
+ hPrint stderr $ sort (map (ml_hs_file . ms_location) (map emsModSummary (rights emss)))
writeMod :: [String] -> IO ()
writeMod src@(head -> stripPrefix "module " -> Just (takeWhile (/=' ') -> mod))
diff --git a/testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs b/testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs
index 732321935b..4f0f4d33bb 100644
--- a/testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs
+++ b/testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs
@@ -6,6 +6,7 @@
import GHC
import GHC.Driver.Make
import GHC.Driver.Session
+import GHC.Unit.Module.ModSummary (ExtendedModSummary(..))
import GHC.Utils.Outputable
import GHC.Utils.Exception (ExceptionMonad)
import GHC.Data.Bag
@@ -169,7 +170,7 @@ go label mods cnd =
-- liftIO $ hPutStrLn stderr $ showSDoc (hsc_dflags hsc_env) $ ppr $ rights emss
-- liftIO $ hPrint stderr $ bagToList $ unionManyBags $ lefts emss
- it label $ cnd (rights emss)
+ it label $ cnd (map emsModSummary (rights emss))
writeMod :: [String] -> IO ()
diff --git a/utils/haddock b/utils/haddock
-Subproject 8a5ccf93c53a40abe42134c2282ac9b9d653224
+Subproject e7ee7957a7ac746cfa05d7218fe0c2d1fd27f56