[Git][ghc/ghc][wip/issue-23821] 4 commits: Be more eager in TyCon boot validity checking

Gergő Érdi (@cactus) gitlab at gitlab.haskell.org
Mon Aug 28 02:08:37 UTC 2023



Gergő Érdi pushed to branch wip/issue-23821 at Glasgow Haskell Compiler / GHC


Commits:
1420b8cb by Antoine Leblanc at 2023-08-24T16:18:17-04:00
Be more eager in TyCon boot validity checking

This commit performs boot-file consistency checking for TyCons into
checkValidTyCl. This ensures that we eagerly catch any mismatches,
which prevents the compiler from seeing these inconsistencies and
panicking as a result.

See Note [TyCon boot consistency checking] in GHC.Tc.TyCl.

Fixes #16127

- - - - -
d99c816f by Finley McIlwaine at 2023-08-24T16:18:55-04:00
Refactor estimation of stack info table provenance

This commit greatly refactors the way we compute estimated provenance for stack
info tables. Previously, this process was done using an entirely separate traversal
of the whole Cmm code stream to build the map from info tables to source locations.
The separate traversal is now fused with the Cmm code generation pipeline in
GHC.Driver.Main.

This results in very significant code generation speed ups when -finfo-table-map is
enabled. In testing, this patch reduces code generation times by almost 30% with
-finfo-table-map and -O0, and 60% with -finfo-table-map and -O1 or -O2 .

Fixes #23103

- - - - -
d3e0124c by Finley McIlwaine at 2023-08-24T16:18:55-04:00
Add a test checking overhead of -finfo-table-map

We want to make sure we don't end up with poor codegen performance resulting from
-finfo-table-map again as in #23103. This test adds a performance test tracking
total allocations while compiling ExactPrint with -finfo-table-map.

- - - - -
15fd2738 by Gergő Érdi at 2023-08-28T03:08:31+01:00
If we have multiple defaulting plugins, then we should zonk in between them

after any defaulting has taken place, to avoid a defaulting plugin seeing
a metavariable that has already been filled.

Fixes #23821.

- - - - -


29 changed files:

- compiler/GHC/Driver/GenerateCgIPEStub.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- docs/users_guide/extending_ghc.rst
- testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr
- + testsuite/tests/profiling/perf/Makefile
- + testsuite/tests/profiling/perf/T23103/all.T
- + testsuite/tests/profiling/perf/T23103/info_table_map_perf.stderr
- + testsuite/tests/rename/should_fail/RnFail059.hs
- + testsuite/tests/rename/should_fail/RnFail059.hs-boot
- + testsuite/tests/rename/should_fail/RnFail059_aux.hs
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rename/should_fail/rnfail055.stderr
- + testsuite/tests/rename/should_fail/rnfail059.stderr
- testsuite/tests/roles/should_fail/Roles12.stderr
- testsuite/tests/roles/should_fail/T9204.stderr
- + testsuite/tests/typecheck/T16127/T16127.hs
- + testsuite/tests/typecheck/T16127/T16127.hs-boot
- + testsuite/tests/typecheck/T16127/T16127.stderr
- + testsuite/tests/typecheck/T16127/T16127Helper.hs
- + testsuite/tests/typecheck/T16127/all.T
- testsuite/tests/typecheck/should_fail/T12035.stderr
- testsuite/tests/typecheck/should_fail/T12035j.stderr
- testsuite/tests/typecheck/should_fail/T12042.stderr
- testsuite/tests/typecheck/should_fail/T20588.stderr
- testsuite/tests/typecheck/should_fail/T20588c.stderr
- testsuite/tests/typecheck/should_fail/T3468.stderr


Changes:

=====================================
compiler/GHC/Driver/GenerateCgIPEStub.hs
=====================================
@@ -1,21 +1,19 @@
 {-# LANGUAGE GADTs         #-}
 {-# LANGUAGE TupleSections #-}
 
-module GHC.Driver.GenerateCgIPEStub (generateCgIPEStub) where
+module GHC.Driver.GenerateCgIPEStub (generateCgIPEStub, lookupEstimatedTicks) where
 
 import Data.Map.Strict (Map)
 import qualified Data.Map.Strict as Map
-import Data.Maybe (mapMaybe, listToMaybe)
 import Data.Semigroup ((<>))
 import GHC.Cmm
-import GHC.Cmm.CLabel (CLabel)
-import GHC.Cmm.Dataflow (Block, C, O)
+import GHC.Cmm.CLabel (CLabel, mkAsmTempLabel)
+import GHC.Cmm.Dataflow (O)
 import GHC.Cmm.Dataflow.Block (blockSplit, blockToList)
 import GHC.Cmm.Dataflow.Collections
-import GHC.Cmm.Dataflow.Label (Label, LabelMap)
+import GHC.Cmm.Dataflow.Label (Label)
 import GHC.Cmm.Info.Build (emptySRT)
 import GHC.Cmm.Pipeline (cmmPipeline)
-import GHC.Data.Maybe (firstJusts)
 import GHC.Data.Stream (Stream, liftIO)
 import qualified GHC.Data.Stream as Stream
 import GHC.Driver.Env (hsc_dflags, hsc_logger)
@@ -26,7 +24,7 @@ import GHC.Driver.Config.StgToCmm
 import GHC.Driver.Config.Cmm
 import GHC.Prelude
 import GHC.Runtime.Heap.Layout (isStackRep)
-import GHC.Settings (Platform, platformTablesNextToCode)
+import GHC.Settings (platformTablesNextToCode)
 import GHC.StgToCmm.Monad (getCmm, initC, runC, initFCodeState)
 import GHC.StgToCmm.Prof (initInfoTableProv)
 import GHC.StgToCmm.Types (CmmCgInfos (..), ModuleLFInfos)
@@ -58,10 +56,16 @@ by `generateCgIPEStub`.
 
 This leads to the question: How to figure out the source location of a return frame?
 
-While the lookup algorithms when tables-next-to-code is on/off differ in details, they have in
-common that we want to lookup the `CmmNode.CmmTick` (containing a `SourceNote`) that is nearest
-(before) the usage of the return frame's label. (Which label and label type is used differs between
-these two use cases.)
+The algorithm for determining source locations for stack info tables is implemented in
+`lookupEstimatedTicks` as two passes over every 'CmmGroupSRTs'. The first pass generates estimated
+source locations for any labels potentially corresponding to stack info tables in the Cmm code. The
+second pass walks over the Cmm decls and creates an entry in the IPE map for every info table,
+looking up source locations for stack info tables in the map generated during the first pass.
+
+The rest of this note will document exactly how the first pass generates the map from labels to
+estimated source positions. The algorithms are different depending on whether tables-next-to-code
+is on or off. Both algorithms have in common that we are looking for a `CmmNode.CmmTick`
+(containing a `SourceNote`) that is near what we estimate to be the label of a return stack frame.
 
 With tables-next-to-code
 ~~~~~~~~~~~~~~~~~~~~~~~~
@@ -113,15 +117,15 @@ for a detailed explanation.
 Here we use the fact, that calls (represented by `CmmNode.CmmCall`) are always closed on exit
 (`CmmNode O C`, `O` means open, `C` closed). In other words, they are always at the end of a block.
 
-So, given a stack represented info table (likely representing a return frame, but this isn't completely
-sure as there are e.g. update frames, too) with it's label (`c18g` in the example above) and a `CmmGraph`:
-  - Look at the end of every block, if it's a `CmmNode.CmmCall` returning to the continuation with the
-    label of the return frame.
-  - If there's such a call, lookup the nearest `CmmNode.CmmTick` by traversing the middle part of the block
-    backwards (from end to beginning).
-  - Take the first `CmmNode.CmmTick` that contains a `Tickish.SourceNote` and return it's payload as
-    `IpeSourceLocation`. (There are other `Tickish` constructors like `ProfNote` or `HpcTick`, these are
-    ignored.)
+So, given a `CmmGraph`:
+  - Look at the end of every block: If it is a `CmmNode.CmmCall` returning to some label, lookup
+    the nearest `CmmNode.CmmTick` by traversing the middle part of the block backwards (from end to
+    beginning).
+  - Take the first `CmmNode.CmmTick` that contains a `Tickish.SourceNote` and map the label we
+    found to it's payload as an `IpeSourceLocation`. (There are other `Tickish` constructors like
+    `ProfNote` or `HpcTick`, these are ignored.)
+
+See `labelsToSourcesWithTNTC` for the implementation of this algorithm.
 
 Without tables-next-to-code
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -176,16 +180,27 @@ In this example we have to lookup `//tick src<Main.hs:20:9-13>` for the return f
 Notice, that this cannot be done with the `Label` `c18M`, but with the `CLabel` `block_c18M_info`
 (`label: block_c18M_info` is actually a `CLabel`).
 
-The find the tick:
-  - Every `Block` is checked from top (first) to bottom (last) node for an assignment like
-   `I64[Sp - 24] = block_c18M_info;`. The lefthand side is actually ignored.
-  - If such an assignment is found the search is over, because the payload (content of
-    `Tickish.SourceNote`, represented as `IpeSourceLocation`) of last visited tick is always
-    remembered in a `Maybe`.
+Given a `CmmGraph`:
+  - Check every `CmmBlock` from top (first) to bottom (last).
+  - If a `CmmTick` holding a `SourceNote` is found, remember the source location in the tick.
+  - If an assignment of the form `... = block_c18M_info;` (a `CmmStore` whose RHS is a
+    `CmmLit (CmmLabel l)`) is found, map that label to the most recently visited source note's
+    location.
+
+See `labelsToSourcesSansTNTC` for the implementation of this algorithm.
 -}
 
-generateCgIPEStub :: HscEnv -> Module -> InfoTableProvMap -> Stream IO CmmGroupSRTs (NonCaffySet, ModuleLFInfos) -> Stream IO CmmGroupSRTs CmmCgInfos
-generateCgIPEStub hsc_env this_mod denv s = do
+generateCgIPEStub
+  :: HscEnv
+  -> Module
+  -> InfoTableProvMap
+  -> ( NonCaffySet
+     , ModuleLFInfos
+     , Map CmmInfoTable (Maybe IpeSourceLocation)
+     , IPEStats
+     )
+  -> Stream IO CmmGroupSRTs CmmCgInfos
+generateCgIPEStub hsc_env this_mod denv (nonCaffySet, moduleLFInfos, infoTablesWithTickishes, initStats) = do
   let dflags   = hsc_dflags hsc_env
       platform = targetPlatform dflags
       logger   = hsc_logger hsc_env
@@ -193,24 +208,6 @@ generateCgIPEStub hsc_env this_mod denv s = do
       cmm_cfg  = initCmmConfig dflags
   cgState <- liftIO initC
 
-  -- Collect info tables from the Cmm if -finfo-table-map is enabled. If
-  -- -finfo-table-map is not enabled, infoTablesWithTickishes will be empty. If
-  -- -finfo-table-map-with-stack is enabled, any STACK info tables will be
-  -- mapped to their source locations (See Note [Stacktraces from Info Table
-  -- Provenance Entries (IPE based stack unwinding)]). If
-  -- -finfo-table-map-with-stack is not enabled, we need to track how many STACK
-  -- info tables we have skipped (in case -dipe-stats is enabled). Note that
-  -- this is the only stats tracking we do at this stage, so initStats here
-  -- should only ever contain stats about skipped STACK info tables.
-  let
-    collectFun =
-      if gopt Opt_InfoTableMap dflags then
-        collect platform
-      else
-        collectNothing platform
-
-  ((infoTablesWithTickishes, initStats), (nonCaffySet, moduleLFInfos)) <- Stream.mapAccumL_ collectFun (mempty, mempty) s
-
   -- Yield Cmm for Info Table Provenance Entries (IPEs)
   let denv' = denv {provInfoTables = Map.mapKeys cit_lbl infoTablesWithTickishes}
       ((mIpeStub, ipeCmmGroup), _) = runC (initStgToCmmConfig dflags this_mod) fstate cgState $ getCmm (initInfoTableProv initStats (Map.keys infoTablesWithTickishes) denv')
@@ -232,102 +229,148 @@ generateCgIPEStub hsc_env this_mod denv s = do
       Nothing -> return mempty
 
   return CmmCgInfos {cgNonCafs = nonCaffySet, cgLFInfos = moduleLFInfos, cgIPEStub = ipeStub}
-  where
-    -- These functions are applied to the elements of the stream of
-    -- CmmGroupSRTs. 'collect' populates a map from info table to potential
-    -- source location, and is used when -finfo-table-map is supplied.
-    -- 'collectNothing' does nothing and just throws out the stream elements.
-    collect, collectNothing
-      :: Platform
-      -> (Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats)
-      -> CmmGroupSRTs
-      -> IO ((Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats), CmmGroupSRTs)
-    collect platform (!acc, !stats) cmmGroupSRTs = do
-      let
-        blocks = concatMap toBlockList (graphs cmmGroupSRTs)
-        labelsToInfoTables = collectInfoTables cmmGroupSRTs
-        (tablesToTickishes, stats') = mapFoldlWithKey (lookupEstimatedTick platform blocks) (acc, stats) labelsToInfoTables
-      return ((tablesToTickishes, stats'), cmmGroupSRTs)
-    collectNothing _ _ cmmGroupSRTs = pure ((Map.empty, mempty), cmmGroupSRTs)
-
-    collectInfoTables :: CmmGroupSRTs -> LabelMap CmmInfoTable
-    collectInfoTables cmmGroup = foldl' extractInfoTables mapEmpty cmmGroup
-
-    extractInfoTables :: LabelMap CmmInfoTable -> GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph -> LabelMap CmmInfoTable
-    extractInfoTables acc (CmmProc h _ _ _) = acc `mapUnion` info_tbls h
-    extractInfoTables acc _ = acc
-
-    lookupEstimatedTick
-      :: Platform
-      -> [CmmBlock]
-      -> (Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats)
-      -> Label
-      -> CmmInfoTable
-      -> (Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats)
-    lookupEstimatedTick platform blocks (!acc, !stats) infoTableLabel infoTable = do
-      -- All return frame info tables are stack represented, though not all stack represented info
-      -- tables have to be return frames.
-      if (isStackRep . cit_rep) infoTable then
-        if gopt Opt_InfoTableMapWithStack (hsc_dflags hsc_env) then
-          -- This is a STACK info table and we DO want to put it in the info
-          -- table map
-          let
-            findFun =
-              if platformTablesNextToCode platform
-                then findCmmTickishWithTNTC infoTableLabel
-                else findCmmTickishSansTNTC (cit_lbl infoTable)
-            -- Avoid retaining the blocks
-            !srcloc =
-              case firstJusts $ map findFun blocks of
-                Just !srcloc -> Just srcloc
-                Nothing -> Nothing
-          in
-            (Map.insert infoTable srcloc acc, stats)
-        else
-          -- This is a STACK info table but we DO NOT want to put it in the info
-          -- table map (-fno-info-table-map-with-stack was given), track it as
-          -- skipped
-            (acc, stats <> skippedIpeStats)
 
+-- | Given:
+--   * an initial mapping from info tables to possible source locations,
+--   * initial 'IPEStats',
+--   * a 'CmmGroupSRTs',
+--
+-- map every info table listed in the 'CmmProc's of the group to their possible
+-- source locations and update 'IPEStats' for skipped stack info tables (in case
+-- both -finfo-table-map and -fno-info-table-map-with-stack were given). See:
+-- Note [Stacktraces from Info Table Provenance Entries (IPE based stack unwinding)]
+--
+-- Note: While it would be cleaner if we could keep the recursion and
+-- accumulation internal to this function, this cannot be done without
+-- separately traversing stream of 'CmmGroupSRTs' in 'GHC.Driver.Main'. The
+-- initial implementation of this logic did such a thing, and code generation
+-- performance suffered considerably as a result (see #23103).
+lookupEstimatedTicks
+  :: HscEnv
+  -> Map CmmInfoTable (Maybe IpeSourceLocation)
+  -> IPEStats
+  -> CmmGroupSRTs
+  -> IO (Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats)
+lookupEstimatedTicks hsc_env ipes stats cmm_group_srts =
+    -- Pass 2: Create an entry in the IPE map for every info table listed in
+    -- this CmmGroupSRTs. If the info table is a stack info table and
+    -- -finfo-table-map-with-stack is enabled, look up its estimated source
+    -- location in the map generate during Pass 1. If the info table is a stack
+    -- info table and -finfo-table-map-with-stack is not enabled, skip the table
+    -- and note it as skipped in the IPE stats. If the info table is not a stack
+    -- info table, insert into the IPE map with no source location information
+    -- (for now; see `convertInfoProvMap` in GHC.StgToCmm.Utils to see how source
+    -- locations for these tables get filled in)
+    pure $ foldl' collectInfoTables (ipes, stats) cmm_group_srts
+  where
+    dflags = hsc_dflags hsc_env
+    platform = targetPlatform dflags
+
+    -- Pass 1: Map every label meeting the conditions described in Note
+    -- [Stacktraces from Info Table Provenance Entries (IPE based stack
+    -- unwinding)] to the estimated source location (also as described in the
+    -- aformentioned note)
+    --
+    -- Note: It's important that this remains a thunk so we do not compute this
+    -- map if -fno-info-table-with-stack is given
+    labelsToSources :: Map CLabel IpeSourceLocation
+    labelsToSources =
+      if platformTablesNextToCode platform then
+        foldl' labelsToSourcesWithTNTC Map.empty cmm_group_srts
       else
-        -- This is not a STACK info table, so put it in the map with no source
-        -- location (for now)
-        (Map.insert infoTable Nothing acc, stats)
+        foldl' labelsToSourcesSansTNTC Map.empty cmm_group_srts
 
-    graphs :: CmmGroupSRTs -> [CmmGraph]
-    graphs = foldl' go []
+    collectInfoTables
+      :: (Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats)
+      -> GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph
+      -> (Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats)
+    collectInfoTables (!acc, !stats) (CmmProc h _ _ _) =
+        mapFoldlWithKey go (acc, stats) (info_tbls h)
       where
-        go :: [CmmGraph] -> GenCmmDecl d h CmmGraph -> [CmmGraph]
-        go acc (CmmProc _ _ _ g) = g : acc
-        go acc _ = acc
-
-    findCmmTickishWithTNTC :: Label -> Block CmmNode C C -> Maybe IpeSourceLocation
-    findCmmTickishWithTNTC label block = do
-      let (_, middleBlock, endBlock) = blockSplit block
-
-      isCallWithReturnFrameLabel endBlock label
-      lastTickInBlock middleBlock
+        go :: (Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats)
+           -> Label
+           -> CmmInfoTable
+           -> (Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats)
+        go (!acc, !stats) lbl' tbl =
+          let
+            lbl =
+              if platformTablesNextToCode platform then
+                -- TNTC case, the mapped CLabel will be the result of
+                -- mkAsmTempLabel on the info table label
+                mkAsmTempLabel lbl'
+              else
+                -- Non-TNTC case, the mapped CLabel will be the CLabel of the
+                -- info table itself
+                cit_lbl tbl
+          in
+            if (isStackRep . cit_rep) tbl then
+              if gopt Opt_InfoTableMapWithStack dflags then
+                -- This is a stack info table and we DO want to put it in the
+                -- info table map
+                (Map.insert tbl (Map.lookup lbl labelsToSources) acc, stats)
+              else
+                -- This is a stack info table but we DO NOT want to put it in
+                -- the info table map (-fno-info-table-map-with-stack was
+                -- given), track it as skipped
+                (acc, stats <> skippedIpeStats)
+            else
+              -- This is not a stack info table, so put it in the map with no
+              -- source location (for now)
+              (Map.insert tbl Nothing acc, stats)
+    collectInfoTables (!acc, !stats) _ = (acc, stats)
+
+-- | See Note [Stacktraces from Info Table Provenance Entries (IPE based stack unwinding)]
+labelsToSourcesWithTNTC
+  :: Map CLabel IpeSourceLocation
+  -> GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph
+  -> Map CLabel IpeSourceLocation
+labelsToSourcesWithTNTC acc (CmmProc _ _ _ cmm_graph) =
+    foldl' go acc (toBlockList cmm_graph)
+  where
+    go :: Map CLabel IpeSourceLocation -> CmmBlock -> Map CLabel IpeSourceLocation
+    go acc block =
+        case (,) <$> returnFrameLabel <*> lastTickInBlock of
+          Just (clabel, src_loc) -> Map.insert clabel src_loc acc
+          Nothing -> acc
       where
-        isCallWithReturnFrameLabel :: CmmNode O C -> Label -> Maybe ()
-        isCallWithReturnFrameLabel (CmmCall _ (Just l) _ _ _ _) clabel | l == clabel = Just ()
-        isCallWithReturnFrameLabel _ _ = Nothing
-
-        lastTickInBlock block =
-          listToMaybe $
-              mapMaybe maybeTick $ (reverse . blockToList) block
-
-        maybeTick :: CmmNode O O -> Maybe IpeSourceLocation
-        maybeTick (CmmTick (SourceNote span name)) = Just (span, name)
-        maybeTick _ = Nothing
-
-    findCmmTickishSansTNTC :: CLabel -> Block CmmNode C C -> Maybe IpeSourceLocation
-    findCmmTickishSansTNTC cLabel block = do
-      let (_, middleBlock, _) = blockSplit block
-      find cLabel (blockToList middleBlock) Nothing
+        (_, middleBlock, endBlock) = blockSplit block
+
+        returnFrameLabel :: Maybe CLabel
+        returnFrameLabel =
+          case endBlock of
+            (CmmCall _ (Just l) _ _ _ _) -> Just $ mkAsmTempLabel l
+            _ -> Nothing
+
+        lastTickInBlock = foldr maybeTick Nothing (blockToList middleBlock)
+
+        maybeTick :: CmmNode O O -> Maybe IpeSourceLocation -> Maybe IpeSourceLocation
+        maybeTick _ s@(Just _) = s
+        maybeTick (CmmTick (SourceNote span name)) Nothing = Just (span, name)
+        maybeTick _ _ = Nothing
+labelsToSourcesWithTNTC acc _ = acc
+
+-- | See Note [Stacktraces from Info Table Provenance Entries (IPE based stack unwinding)]
+labelsToSourcesSansTNTC
+  :: Map CLabel IpeSourceLocation
+  -> GenCmmDecl RawCmmStatics CmmTopInfo CmmGraph
+  -> Map CLabel IpeSourceLocation
+labelsToSourcesSansTNTC acc (CmmProc _ _ _ cmm_graph) =
+    foldl' go acc (toBlockList cmm_graph)
+  where
+    go :: Map CLabel IpeSourceLocation -> CmmBlock -> Map CLabel IpeSourceLocation
+    go acc block = fst $ foldl' collectLabels (acc, Nothing) (blockToList middleBlock)
       where
-        find :: CLabel -> [CmmNode O O] -> Maybe IpeSourceLocation -> Maybe IpeSourceLocation
-        find label (b : blocks) lastTick = case b of
-          (CmmStore _ (CmmLit (CmmLabel l)) _) -> if label == l then lastTick else find label blocks lastTick
-          (CmmTick (SourceNote span name)) -> find label blocks $ Just (span, name)
-          _ -> find label blocks lastTick
-        find _ [] _ = Nothing
+        (_, middleBlock, _) = blockSplit block
+
+        collectLabels
+          :: (Map CLabel IpeSourceLocation, Maybe IpeSourceLocation)
+          -> CmmNode O O
+          -> (Map CLabel IpeSourceLocation, Maybe IpeSourceLocation)
+        collectLabels (!acc, lastTick) b =
+          case (b, lastTick) of
+            (CmmStore _ (CmmLit (CmmLabel l)) _, Just src_loc) ->
+              (Map.insert l src_loc acc, Nothing)
+            (CmmTick (SourceNote span name), _) ->
+              (acc, Just (span, name))
+            _ -> (acc, lastTick)
+labelsToSourcesSansTNTC acc _ = acc
\ No newline at end of file


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -136,7 +136,7 @@ import GHC.Driver.Config.StgToJS  (initStgToJSConfig)
 import GHC.Driver.Config.Diagnostic
 import GHC.Driver.Config.Tidy
 import GHC.Driver.Hooks
-import GHC.Driver.GenerateCgIPEStub (generateCgIPEStub)
+import GHC.Driver.GenerateCgIPEStub (generateCgIPEStub, lookupEstimatedTicks)
 
 import GHC.Runtime.Context
 import GHC.Runtime.Interpreter
@@ -245,7 +245,6 @@ import GHC.Types.Name
 import GHC.Types.Name.Cache ( initNameCache )
 import GHC.Types.Name.Reader
 import GHC.Types.Name.Ppr
-import GHC.Types.Name.Set (NonCaffySet)
 import GHC.Types.TyThing
 import GHC.Types.HpcInfo
 import GHC.Types.Unique.Supply (uniqFromTag)
@@ -280,11 +279,11 @@ import Control.Monad
 import Data.IORef
 import System.FilePath as FilePath
 import System.Directory
+import qualified Data.Map as M
+import Data.Map (Map)
 import qualified Data.Set as S
 import Data.Set (Set)
-import Data.Functor ((<&>))
 import Control.DeepSeq (force)
-import Data.Bifunctor (first)
 import Data.List.NonEmpty (NonEmpty ((:|)))
 import GHC.Unit.Module.WholeCoreBindings
 import GHC.Types.TypeEnv
@@ -295,8 +294,10 @@ import Data.Time
 import System.IO.Unsafe ( unsafeInterleaveIO )
 import GHC.Iface.Env ( trace_if )
 import GHC.Stg.InferTags.TagSig (seqTagSig)
+import GHC.StgToCmm.Utils (IPEStats)
 import GHC.Types.Unique.FM
 import GHC.Types.Unique.DFM
+import GHC.Cmm.Config (CmmConfig)
 
 
 {- **********************************************************************
@@ -2126,21 +2127,41 @@ doCodeGen hsc_env this_mod denv data_tycons
 
         cmm_config = initCmmConfig dflags
 
-        pipeline_stream :: Stream IO CmmGroupSRTs (NonCaffySet, ModuleLFInfos)
+        pipeline_stream :: Stream IO CmmGroupSRTs CmmCgInfos
         pipeline_stream = do
-          (non_cafs,  lf_infos) <-
+          ((mod_srt_info, ipes, ipe_stats), lf_infos) <-
             {-# SCC "cmmPipeline" #-}
-            Stream.mapAccumL_ (cmmPipeline logger cmm_config) (emptySRT this_mod) ppr_stream1
-              <&> first (srtMapNonCAFs . moduleSRTMap)
-
-          return (non_cafs, lf_infos)
+            Stream.mapAccumL_ (pipeline_action logger cmm_config) (emptySRT this_mod, M.empty, mempty) ppr_stream1
+          let nonCaffySet = srtMapNonCAFs (moduleSRTMap mod_srt_info)
+          cmmCgInfos <- generateCgIPEStub hsc_env this_mod denv (nonCaffySet, lf_infos, ipes, ipe_stats)
+          return cmmCgInfos
+
+        pipeline_action
+          :: Logger
+          -> CmmConfig
+          -> (ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats)
+          -> CmmGroup
+          -> IO ((ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats), CmmGroupSRTs)
+        pipeline_action logger cmm_config (mod_srt_info, ipes, stats) cmm_group = do
+          (mod_srt_info', cmm_srts) <- cmmPipeline logger cmm_config mod_srt_info cmm_group
+
+          -- If -finfo-table-map is enabled, we precompute a map from info
+          -- tables to source locations. See Note [Mapping Info Tables to Source
+          -- Positions] in GHC.Stg.Debug.
+          (ipes', stats') <-
+            if (gopt Opt_InfoTableMap dflags) then
+              lookupEstimatedTicks hsc_env ipes stats cmm_srts
+            else
+              return (ipes, stats)
+
+          return ((mod_srt_info', ipes', stats'), cmm_srts)
 
         dump2 a = do
           unless (null a) $
             putDumpFileMaybe logger Opt_D_dump_cmm "Output Cmm" FormatCMM (pdoc platform a)
           return a
 
-    return $ Stream.mapM dump2 $ generateCgIPEStub hsc_env this_mod denv pipeline_stream
+    return $ Stream.mapM dump2 pipeline_stream
 
 myCoreToStg :: Logger -> DynFlags -> [Var]
             -> Bool


=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -3590,20 +3590,14 @@ applyDefaultingRules wanteds
        ; tcg_env <- TcS.getGblEnv
        ; let plugins = tcg_defaulting_plugins tcg_env
 
-       ; plugin_defaulted <- if null plugins then return [] else
+       ; (wanteds, plugin_defaulted) <- if null plugins then return (wanteds, []) else
            do {
              ; traceTcS "defaultingPlugins {" (ppr wanteds)
-             ; defaultedGroups <- mapM (run_defaulting_plugin wanteds) plugins
+             ; (wanteds, defaultedGroups) <- mapAccumLM run_defaulting_plugin wanteds plugins
              ; traceTcS "defaultingPlugins }" (ppr defaultedGroups)
-             ; return defaultedGroups
+             ; return (wanteds, defaultedGroups)
              }
 
-       -- If a defaulting plugin solves a tyvar, some of the wanteds
-       -- will have filled-in metavars by now (see #23281). So we
-       -- re-zonk to make sure the built-in defaulting rules don't try
-       -- to solve the same metavars.
-       ; wanteds <- if or plugin_defaulted then TcS.zonkWC wanteds else pure wanteds
-
        ; let groups = findDefaultableGroups info wanteds
 
        ; traceTcS "applyDefaultingRules {" $
@@ -3625,8 +3619,14 @@ applyDefaultingRules wanteds
                     groups
                ; traceTcS "defaultingPlugin " $ ppr defaultedGroups
                ; case defaultedGroups of
-                 [] -> return False
-                 _  -> return True
+                 [] -> return (wanteds, False)
+                 _  -> do
+                     -- If a defaulting plugin solves any tyvars, some of the wanteds
+                     -- will have filled-in metavars by now (see #23281). So we
+                     -- re-zonk to make sure later defaulting doesn't try to solve
+                     -- the same metavars.
+                     wanteds' <- TcS.zonkWC wanteds
+                     return (wanteds', True)
                }
 
 


=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -48,6 +48,7 @@ import GHC.Tc.Zonk.TcType
 import GHC.Tc.TyCl.Utils
 import GHC.Tc.TyCl.Class
 import {-# SOURCE #-} GHC.Tc.TyCl.Instance( tcInstDecls1 )
+import {-# SOURCE #-} GHC.Tc.Module( checkBootDeclM )
 import GHC.Tc.Deriv (DerivInfo(..))
 import GHC.Tc.Gen.HsType
 import GHC.Tc.Instance.Class( AssocInstInfo(..) )
@@ -84,6 +85,7 @@ import GHC.Types.Name.Set
 import GHC.Types.Name.Env
 import GHC.Types.SrcLoc
 import GHC.Types.SourceFile
+import GHC.Types.TypeEnv
 import GHC.Types.Unique
 import GHC.Types.Basic
 import qualified GHC.LanguageExtensions as LangExt
@@ -93,6 +95,7 @@ import GHC.Data.Maybe
 import GHC.Data.List.SetOps( minusList, equivClasses )
 
 import GHC.Unit
+import GHC.Unit.Module.ModDetails
 
 import GHC.Utils.Outputable
 import GHC.Utils.Panic
@@ -209,7 +212,12 @@ tcTyClGroup (TyClGroup { group_tyclds = tyclds
            -- Do it before Step 3 (adding implicit things) because the latter
            -- expects well-formed TyCons
        ; traceTc "Starting validity check" (ppr tyclss)
-       ; tyclss <- concatMapM checkValidTyCl tyclss
+       ; tyclss <- tcExtendTyConEnv tyclss $
+           -- NB: put the TyCons in the environment for validity checking,
+           -- as we might look them up in checkTyConConsistentWithBoot.
+           -- See Note [TyCon boot consistency checking].
+                   concatMapM checkValidTyCl tyclss
+
        ; traceTc "Done validity check" (ppr tyclss)
        ; mapM_ (recoverM (return ()) . checkValidRoleAnnots role_annots) tyclss
            -- See Note [Check role annotations in a second pass]
@@ -4327,6 +4335,7 @@ checkValidTyCl tc
     recoverM recovery_code     $
     do { traceTc "Starting validity for tycon" (ppr tc)
        ; checkValidTyCon tc
+       ; checkTyConConsistentWithBoot tc -- See Note [TyCon boot consistency checking]
        ; traceTc "Done validity for tycon" (ppr tc)
        ; return [tc] }
   where
@@ -4403,6 +4412,49 @@ Some notes:
 --        T2 { f1 :: c, f2 :: c, f3 ::Int } :: T
 -- Here we do not complain about f1,f2 because they are existential
 
+-- | Check that a 'TyCon' is consistent with the one in the hs-boot file,
+-- if any.
+--
+-- See Note [TyCon boot consistency checking].
+checkTyConConsistentWithBoot :: TyCon -> TcM ()
+checkTyConConsistentWithBoot tc =
+  do { gbl_env <- getGblEnv
+     ; let name          = tyConName tc
+           real_thing    = ATyCon tc
+           boot_info     = tcg_self_boot gbl_env
+           boot_type_env = case boot_info of
+             NoSelfBoot            -> emptyTypeEnv
+             SelfBoot boot_details -> md_types boot_details
+           m_boot_info   = lookupTypeEnv boot_type_env name
+     ; case m_boot_info of
+         Nothing         -> return ()
+         Just boot_thing -> checkBootDeclM HsBoot boot_thing real_thing
+     }
+
+{- Note [TyCon boot consistency checking]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We want to throw an error when A.hs and A.hs-boot define a TyCon inconsistently,
+e.g.
+
+  -- A.hs-boot
+  type D :: Type
+  data D
+
+  -- A.hs
+  data D (k :: Type) = MkD
+
+Here A.D and A[boot].D have different kinds, so we must error. In addition, we
+must error eagerly, lest other parts of the compiler witness this inconsistency
+(which was the subject of #16127). To achieve this, we call
+checkTyConIsConsistentWithBoot in checkValidTyCl, which is called in
+GHC.Tc.TyCl.tcTyClGroup.
+
+Note that, when calling checkValidTyCl, we must extend the TyCon environment.
+For example, we could end up comparing the RHS of two type synonym declarations
+to check they are consistent, and these RHS might mention some of the TyCons we
+are validity checking, so they need to be in the environment.
+-}
+
 checkValidTyCon :: TyCon -> TcM ()
 checkValidTyCon tc
   | isPrimTyCon tc   -- Happens when Haddock'ing GHC.Prim


=====================================
compiler/GHC/Tc/TyCl/Utils.hs
=====================================
@@ -1,4 +1,3 @@
-
 {-# LANGUAGE DeriveFunctor #-}
 {-# LANGUAGE TypeFamilies #-}
 


=====================================
docs/users_guide/extending_ghc.rst
=====================================
@@ -1368,8 +1368,7 @@ Defaulting plugins have a single access point in the `GHC.Tc.Types` module
           -- ^ The constraints against which defaults are checked.
         }
 
-    type DefaultingPluginResult = [DefaultingProposal]
-    type FillDefaulting = WantedConstraints -> TcPluginM DefaultingPluginResult
+    type FillDefaulting = WantedConstraints -> TcPluginM [DefaultingProposal]
 
     -- | A plugin for controlling defaulting.
     data DefaultingPlugin = forall s. DefaultingPlugin
@@ -1383,15 +1382,17 @@ Defaulting plugins have a single access point in the `GHC.Tc.Types` module
 
 
 The plugin gets a combination of wanted constraints which can be most easily
-broken down into simple wanted constraints with ``approximateWC``. The result of
-running the plugin should be a ``DefaultingPluginResult``, a list of types that
-should be attempted for a given type variable that is ambiguous in a given
-context. GHC will check if one of the proposals is acceptable in the given
-context and then default to it. The most robust context to provide is the list
-of all wanted constraints that mention the variable you are defaulting. If you
-leave out a constraint, the default will be accepted, and then potentially
-result in a type checker error if it is incompatible with one of the constraints
-you left out. This can be a useful way of forcing a default and reporting errors
+broken down into simple wanted constraints with ``approximateWC``. These wanted
+constraints contain unfilled metavariables which are the ones ambiguous in the
+given context and which the plugin has a chance to solve. The result of
+running the plugin should be a ``[DefaultingProposal]``: a list of types that
+should be attempted for a given type variable. GHC will check if one of the
+proposals is acceptable in the given context and then default to it. The most
+robust context to return in ``deProposalCts`` is the list of all wanted
+constraints that mention the variable you are defaulting. If you leave out a
+constraint, the default will be accepted, and then potentially result in a
+type checker error if it is incompatible with one of the constraints you
+left out. This can be a useful way of forcing a default and reporting errors
 to the user.
 
 There is an example of defaulting lifted types in the GHC test suite. In the


=====================================
testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr
=====================================
@@ -1,39 +1,42 @@
 
 ClosedFam3.hs-boot:7:1: error: [GHC-15843]
-    Type constructor ‘Foo’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type Foo :: * -> *
-                 type family Foo a where
-                     Foo Int = Bool
-                     Foo Double = Char
-      Boot file: type Foo :: * -> *
-                 type family Foo a where
-                     Foo Int = Bool
-    Type family equations do not match:
-      The number of equations differs.
+    • Type constructor ‘Foo’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type Foo :: * -> *
+                   type family Foo a where
+                       Foo Int = Bool
+                       Foo Double = Char
+        Boot file: type Foo :: * -> *
+                   type family Foo a where
+                       Foo Int = Bool
+      Type family equations do not match:
+        The number of equations differs.
+    • In the type family declaration for ‘Foo’
 
 ClosedFam3.hs-boot:10:1: error: [GHC-15843]
-    Type constructor ‘Bar’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type Bar :: * -> *
-                 type family Bar a where
-                     Bar Int = Bool
-                     Bar Double = Double
-      Boot file: type Bar :: * -> *
-                 type family Bar a where
-                     Bar Int = Bool
-                     Bar Double = Char
-    Type family equations do not match:
-      The third equations do not match.
-        The equation right-hand sides don't match.
+    • Type constructor ‘Bar’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type Bar :: * -> *
+                   type family Bar a where
+                       Bar Int = Bool
+                       Bar Double = Double
+        Boot file: type Bar :: * -> *
+                   type family Bar a where
+                       Bar Int = Bool
+                       Bar Double = Char
+      Type family equations do not match:
+        The third equations do not match.
+          The equation right-hand sides don't match.
+    • In the type family declaration for ‘Bar’
 
 ClosedFam3.hs-boot:15:1: error: [GHC-15843]
-    Type constructor ‘Baz’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type Baz :: * -> *
-                 type family Baz a where
-                     Baz Int = Bool
-      Boot file: type Baz :: forall k. k -> *
-                 type family Baz a where
-                     Baz Int = Bool
-    The types have different kinds.
+    • Type constructor ‘Baz’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type Baz :: * -> *
+                   type family Baz a where
+                       Baz Int = Bool
+        Boot file: type Baz :: forall k. k -> *
+                   type family Baz a where
+                       Baz Int = Bool
+      The types have different kinds.
+    • In the type family declaration for ‘Baz’


=====================================
testsuite/tests/profiling/perf/Makefile
=====================================
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
\ No newline at end of file


=====================================
testsuite/tests/profiling/perf/T23103/all.T
=====================================
@@ -0,0 +1,18 @@
+test(
+    'info_table_map_perf',
+    [
+        collect_compiler_stats('bytes allocated',10),
+        extra_files(
+            [
+                '../../../../../utils/check-exact/ExactPrint.hs',
+                '../../../../../utils/check-exact/Lookup.hs',
+                '../../../../../utils/check-exact/Orphans.hs',
+                '../../../../../utils/check-exact/Types.hs',
+                '../../../../../utils/check-exact/Utils.hs',
+            ]
+        ),
+        js_skip
+    ],
+    multimod_compile,
+    ['ExactPrint.hs', '-package ghc -O -finfo-table-map']
+)


=====================================
testsuite/tests/profiling/perf/T23103/info_table_map_perf.stderr
=====================================
@@ -0,0 +1,5 @@
+[1 of 5] Compiling Orphans          ( Orphans.hs, Orphans.o )
+[2 of 5] Compiling Types            ( Types.hs, Types.o )
+[3 of 5] Compiling Lookup           ( Lookup.hs, Lookup.o )
+[4 of 5] Compiling Utils            ( Utils.hs, Utils.o )
+[5 of 5] Compiling ExactPrint       ( ExactPrint.hs, ExactPrint.o )


=====================================
testsuite/tests/rename/should_fail/RnFail059.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE Haskell2010 #-}
+module RnFail059 where
+
+import RnFail059_aux
+
+-- Id with different type
+f1 :: Int -> Float
+f1 = undefined


=====================================
testsuite/tests/rename/should_fail/RnFail059.hs-boot
=====================================
@@ -0,0 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
+module RnFail059 where
+
+f1 :: Float -> Int


=====================================
testsuite/tests/rename/should_fail/RnFail059_aux.hs
=====================================
@@ -0,0 +1,3 @@
+module RnFail059_aux where
+
+import {-# SOURCE #-} RnFail059


=====================================
testsuite/tests/rename/should_fail/all.T
=====================================
@@ -1,4 +1,3 @@
-
 test('rnfail001', normal, compile_fail, [''])
 test('rnfail002', normal, compile_fail, [''])
 test('rnfail003', normal, compile_fail, [''])
@@ -59,6 +58,7 @@ test('rnfail055', [extra_files(['RnFail055.hs', 'RnFail055.hs-boot', 'RnFail055_
 test('rnfail056', normal, compile_fail, [''])
 test('rnfail057', normal, compile_fail, [''])
 test('rnfail058', normal, compile_fail, [''])
+test('rnfail059', [extra_files(['RnFail059.hs', 'RnFail059.hs-boot', 'RnFail059_aux.hs'])], multimod_compile_fail, ['RnFail059', '-v0'])
 
 test('rn_dup', normal, compile_fail, [''])
 test('T495', normal, compile_fail, [''])


=====================================
testsuite/tests/rename/should_fail/rnfail055.stderr
=====================================
@@ -1,121 +1,146 @@
-
 RnFail055.hs:2:73: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)]
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
 RnFail055.hs-boot:2:73: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)]
     -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
 
-RnFail055.hs-boot:5:1: error: [GHC-11890]
-    Identifier ‘f1’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: f1 :: Int -> Float
-      Boot file: f1 :: Float -> Int
-    The two types are different.
-
 RnFail055.hs-boot:7:1: error: [GHC-15843]
-    Type constructor ‘S1’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type S1 :: * -> * -> *
-                 type S1 a b = (a, b)
-      Boot file: type S1 :: * -> * -> * -> *
-                 type S1 a b c = (a, b)
-    The types have different kinds.
+    • Type constructor ‘S1’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type S1 :: * -> * -> *
+                   type S1 a b = (a, b)
+        Boot file: type S1 :: * -> * -> * -> *
+                   type S1 a b c = (a, b)
+      The types have different kinds.
+    • In the type synonym declaration for ‘S1’
 
 RnFail055.hs-boot:9:1: error: [GHC-15843]
-    Type constructor ‘S2’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type S2 :: * -> * -> *
-                 type S2 a b = forall a1. (a1, b)
-      Boot file: type S2 :: * -> * -> *
-                 type S2 a b = forall b1. (a, b1)
-    The roles do not match.
-    NB: roles on abstract types default to ‘representational’ in hs-boot files.
+    • Type constructor ‘S2’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type S2 :: * -> * -> *
+                   type S2 a b = forall a1. (a1, b)
+        Boot file: type S2 :: * -> * -> *
+                   type S2 a b = forall b1. (a, b1)
+      The roles do not match.
+      NB: roles on abstract types default to ‘representational’ in hs-boot files.
+    • In the type synonym declaration for ‘S2’
 
 RnFail055.hs-boot:13:1: error: [GHC-15843]
-    Type constructor ‘T1’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type T1 :: * -> * -> *
-                 data T1 a b = T1 [b] [a]
-      Boot file: type T1 :: * -> * -> *
-                 data T1 a b = T1 [a] [b]
-    The constructors do not match: The types for ‘T1’ differ.
+    • Type constructor ‘T1’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type T1 :: * -> * -> *
+                   data T1 a b = T1 [b] [a]
+        Boot file: type T1 :: * -> * -> *
+                   data T1 a b = T1 [a] [b]
+      The constructors do not match: The types for ‘T1’ differ.
+    • In the data type declaration for ‘T1’
 
 RnFail055.hs-boot:15:1: error: [GHC-15843]
-    Type constructor ‘T2’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type role T2 representational nominal
-                 type T2 :: * -> * -> *
-                 data Eq b => T2 a b = T2 a
-      Boot file: type role T2 nominal phantom
-                 type T2 :: * -> * -> *
-                 data Eq a => T2 a b = T2 a
-    The roles do not match.
-    NB: roles on abstract types default to ‘representational’ in hs-boot files.
-    The datatype contexts do not match.
-    The constructors do not match: The types for ‘T2’ differ.
+    • Type constructor ‘T2’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type role T2 representational nominal
+                   type T2 :: * -> * -> *
+                   data Eq b => T2 a b = T2 a
+        Boot file: type role T2 nominal phantom
+                   type T2 :: * -> * -> *
+                   data Eq a => T2 a b = T2 a
+      The roles do not match.
+      NB: roles on abstract types default to ‘representational’ in hs-boot files.
+      The datatype contexts do not match.
+      The constructors do not match: The types for ‘T2’ differ.
+    • In the data type declaration for ‘T2’
 
-RnFail055.hs-boot:17:11: error: [GHC-91999]
-    ‘T3’ is exported by the hs-boot file, but not exported by the implementing module.
+RnFail055.hs-boot:17:1: error: [GHC-15843]
+    • Type constructor ‘T3’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type T3 :: *
+                   data T3 = T3'
+        Boot file: type T3 :: *
+                   data T3 = T3
+      The constructors do not match: The names ‘T3’ and ‘T3'’ differ.
+    • In the data type declaration for ‘T3’
 
-RnFail055.hs-boot:18:12: error: [GHC-91999]
-    ‘T3'’ is exported by the hs-boot file, but not exported by the implementing module.
+RnFail055.hs-boot:18:1: error: [GHC-15843]
+    • Type constructor ‘T3'’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type T3' :: *
+                   data T3' = T3
+        Boot file: type T3' :: *
+                   data T3' = T3'
+      The constructors do not match: The names ‘T3'’ and ‘T3’ differ.
+    • In the data type declaration for ‘T3'’
 
 RnFail055.hs-boot:22:1: error: [GHC-15843]
-    Type constructor ‘T5’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type T5 :: * -> *
-                 data T5 a = T5 {field5 :: a}
-      Boot file: type T5 :: * -> *
-                 data T5 a = T5 a
-    The constructors do not match:
-      The record label lists for ‘T5’ differ.
+    • Type constructor ‘T5’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type T5 :: * -> *
+                   data T5 a = T5 {field5 :: a}
+        Boot file: type T5 :: * -> *
+                   data T5 a = T5 a
+      The constructors do not match:
+        The record label lists for ‘T5’ differ.
+    • In the data type declaration for ‘T5’
 
 RnFail055.hs-boot:24:1: error: [GHC-15843]
-    Type constructor ‘T6’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type T6 :: *
-                 data T6 = T6 Int
-      Boot file: type T6 :: *
-                 data T6 = T6 !Int
-    The constructors do not match:
-      The strictness annotations for ‘T6’ differ.
+    • Type constructor ‘T6’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type T6 :: *
+                   data T6 = T6 Int
+        Boot file: type T6 :: *
+                   data T6 = T6 !Int
+      The constructors do not match:
+        The strictness annotations for ‘T6’ differ.
+    • In the data type declaration for ‘T6’
 
 RnFail055.hs-boot:26:1: error: [GHC-15843]
-    Type constructor ‘T7’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type role T7 phantom
-                 type T7 :: * -> *
-                 data T7 a = forall a1. T7 a1
-      Boot file: type T7 :: * -> *
-                 data T7 a = forall b. T7 a
-    The roles do not match.
-    NB: roles on abstract types default to ‘representational’ in hs-boot files.
-    The constructors do not match: The types for ‘T7’ differ.
+    • Type constructor ‘T7’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type role T7 phantom
+                   type T7 :: * -> *
+                   data T7 a = forall a1. T7 a1
+        Boot file: type T7 :: * -> *
+                   data T7 a = forall b. T7 a
+      The roles do not match.
+      NB: roles on abstract types default to ‘representational’ in hs-boot files.
+      The constructors do not match: The types for ‘T7’ differ.
+    • In the data type declaration for ‘T7’
 
-RnFail055.hs-boot:28:22: error: [GHC-91999]
-    ‘RnFail055.m1’ is exported by the hs-boot file, but not exported by the implementing module.
+RnFail055.hs-boot:28:1: error: [GHC-15843]
+    • Class ‘C1’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type C1 :: * -> * -> Constraint
+                   class C1 a b
+        Boot file: type C1 :: * -> * -> Constraint
+                   class C1 a b where
+                     RnFail055.m1 :: a -> b
+                     {-# MINIMAL m1 #-}
+      The class methods do not match:
+        The number of class methods differs.
+    • In the class declaration for ‘C1’
 
 RnFail055.hs-boot:29:1: error: [GHC-15843]
-    Class ‘C2’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type C2 :: * -> * -> Constraint
-                 class C2 a b where
-                   m2 :: a -> b
-                   m2' :: a -> b
-                   {-# MINIMAL m2, m2' #-}
-      Boot file: type C2 :: * -> * -> Constraint
-                 class C2 a b where
-                   m2 :: a -> b
-                   {-# MINIMAL m2 #-}
-    The class methods do not match:
-      The number of class methods differs.
-    The MINIMAL pragmas are not compatible.
+    • Class ‘C2’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type C2 :: * -> * -> Constraint
+                   class C2 a b where
+                     m2 :: a -> b
+                     m2' :: a -> b
+                     {-# MINIMAL m2, m2' #-}
+        Boot file: type C2 :: * -> * -> Constraint
+                   class C2 a b where
+                     m2 :: a -> b
+                     {-# MINIMAL m2 #-}
+      The class methods do not match:
+        The number of class methods differs.
+      The MINIMAL pragmas are not compatible.
+    • In the class declaration for ‘C2’
 
 RnFail055.hs-boot:30:1: error: [GHC-15843]
-    Class ‘C3’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type C3 :: * -> Constraint
-                 class (Eq a, Ord a) => C3 a
-      Boot file: type C3 :: * -> Constraint
-                 class (Ord a, Eq a) => C3 a
-    The superclass constraints do not match.
+    • Class ‘C3’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type C3 :: * -> Constraint
+                   class (Eq a, Ord a) => C3 a
+        Boot file: type C3 :: * -> Constraint
+                   class (Ord a, Eq a) => C3 a
+      The superclass constraints do not match.
+    • In the class declaration for ‘C3’


=====================================
testsuite/tests/rename/should_fail/rnfail059.stderr
=====================================
@@ -0,0 +1,6 @@
+RnFail059.hs-boot:4:1: error: [GHC-11890]
+    Identifier ‘f1’ has conflicting definitions in the module
+    and its hs-boot file.
+    Main module: f1 :: Int -> Float
+      Boot file: f1 :: Float -> Int
+    The two types are different.


=====================================
testsuite/tests/roles/should_fail/Roles12.stderr
=====================================
@@ -1,11 +1,12 @@
 
 Roles12.hs:6:1: error: [GHC-15843]
-    Type constructor ‘T’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type role T phantom
-                 type T :: * -> *
-                 data T a
-      Boot file: type T :: * -> *
-                 data T a
-    The roles do not match.
-    NB: roles on abstract types default to ‘representational’ in hs-boot files.
+    • Type constructor ‘T’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type role T phantom
+                   type T :: * -> *
+                   data T a
+        Boot file: type T :: * -> *
+                   data T a
+      The roles do not match.
+      NB: roles on abstract types default to ‘representational’ in hs-boot files.
+    • In the data type declaration for ‘T’


=====================================
testsuite/tests/roles/should_fail/T9204.stderr
=====================================
@@ -1,11 +1,12 @@
 
 T9204.hs:7:1: error: [GHC-15843]
-    Type constructor ‘D’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type role D phantom
-                 type D :: * -> *
-                 data D a
-      Boot file: type D :: * -> *
-                 data D a
-    The roles do not match.
-    NB: roles on abstract types default to ‘representational’ in hs-boot files.
+    • Type constructor ‘D’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type role D phantom
+                   type D :: * -> *
+                   data D a
+        Boot file: type D :: * -> *
+                   data D a
+      The roles do not match.
+      NB: roles on abstract types default to ‘representational’ in hs-boot files.
+    • In the data type declaration for ‘D’


=====================================
testsuite/tests/typecheck/T16127/T16127.hs
=====================================
@@ -0,0 +1,8 @@
+module T16127 where
+
+import T16127Helper
+
+data E a
+
+g :: E ()
+g = _


=====================================
testsuite/tests/typecheck/T16127/T16127.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module T16127 where
+
+data E s a


=====================================
testsuite/tests/typecheck/T16127/T16127.stderr
=====================================
@@ -0,0 +1,14 @@
+[1 of 3] Compiling T16127[boot]     ( T16127.hs-boot, T16127.o-boot )
+[2 of 3] Compiling T16127Helper     ( T16127Helper.hs, T16127Helper.o )
+[3 of 3] Compiling T16127           ( T16127.hs, T16127.o )
+
+T16127.hs-boot:3:1: [GHC-15843]
+     Type constructor ‘E’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type role E phantom
+                   type E :: forall {k}. k -> *
+                   data E a
+        Boot file: type E :: forall {k} {k1}. k -> k1 -> *
+                   data E s a
+      The types have different kinds.
+     In the data type declaration for ‘E’


=====================================
testsuite/tests/typecheck/T16127/T16127Helper.hs
=====================================
@@ -0,0 +1,6 @@
+module T16127Helper where
+
+import {-# SOURCE #-} T16127
+
+f :: E () ()
+f = undefined


=====================================
testsuite/tests/typecheck/T16127/all.T
=====================================
@@ -0,0 +1 @@
+test('T16127', normal, multimod_compile_fail, ['T16127', ''])


=====================================
testsuite/tests/typecheck/should_fail/T12035.stderr
=====================================
@@ -1,8 +1,9 @@
 
 T12035.hs-boot:2:1: error: [GHC-15843]
-    Type constructor ‘T’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type T :: *
-                 type T = Bool
-      Boot file: type T :: *
-                 data T
+    • Type constructor ‘T’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type T :: *
+                   type T = Bool
+        Boot file: type T :: *
+                   data T
+    • In the type synonym declaration for ‘T’


=====================================
testsuite/tests/typecheck/should_fail/T12035j.stderr
=====================================
@@ -1,8 +1,9 @@
 
 T12035.hs-boot:2:1: error: [GHC-15843]
-    Type constructor ‘T’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type T :: *
-                 type T = Bool
-      Boot file: type T :: *
-                 data T
+    • Type constructor ‘T’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type T :: *
+                   type T = Bool
+        Boot file: type T :: *
+                   data T
+    • In the type synonym declaration for ‘T’


=====================================
testsuite/tests/typecheck/should_fail/T12042.stderr
=====================================
@@ -3,9 +3,10 @@
 [3 of 3] Compiling T12042           ( T12042.hs, T12042.o )
 
 T12042.hs-boot:2:1: error: [GHC-15843]
-    Type constructor ‘S’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type S :: *
-                 type S = R
-      Boot file: type S :: *
-                 data S
+    • Type constructor ‘S’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type S :: *
+                   type S = R
+        Boot file: type S :: *
+                   data S
+    • In the type synonym declaration for ‘S’


=====================================
testsuite/tests/typecheck/should_fail/T20588.stderr
=====================================
@@ -1,29 +1,31 @@
 
 T20588.hs-boot:8:1: error: [GHC-15843]
-    Class ‘C’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type C :: * -> Constraint
-                 class C a where
-                   meth :: a -> a
-                   {-# MINIMAL meth #-}
-      Boot file: type C :: * -> Constraint
-                 class C a where
-                   meth :: a -> a
-                   {-# MINIMAL meth #-}
-    The class methods do not match:
-      The default methods associated with ‘meth’ are different.
+    • Class ‘C’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type C :: * -> Constraint
+                   class C a where
+                     meth :: a -> a
+                     {-# MINIMAL meth #-}
+        Boot file: type C :: * -> Constraint
+                   class C a where
+                     meth :: a -> a
+                     {-# MINIMAL meth #-}
+      The class methods do not match:
+        The default methods associated with ‘meth’ are different.
+    • In the class declaration for ‘C’
 
 T20588.hs-boot:11:1: error: [GHC-15843]
-    Class ‘D’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type D :: * -> Constraint
-                 class D a where
-                   type T :: * -> *
-                   type family T a
-                     Default: Int
-      Boot file: type D :: * -> Constraint
-                 class D a where
-                   type T :: * -> *
-                   type family T a
-    The associated types do not match:
-      The types of the second associated type default differ.
+    • Class ‘D’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type D :: * -> Constraint
+                   class D a where
+                     type T :: * -> *
+                     type family T a
+                       Default: Int
+        Boot file: type D :: * -> Constraint
+                   class D a where
+                     type T :: * -> *
+                     type family T a
+      The associated types do not match:
+        The types of the second associated type default differ.
+    • In the class declaration for ‘D’


=====================================
testsuite/tests/typecheck/should_fail/T20588c.stderr
=====================================
@@ -1,14 +1,15 @@
 
 T20588c.hs-boot:7:1: error: [GHC-15843]
-    Class ‘C’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type C :: * -> Constraint
-                 class C a where
-                   meth :: a
-                   default meth :: Monoid a => a
-      Boot file: type C :: * -> Constraint
-                 class C a where
-                   meth :: a
-                   {-# MINIMAL meth #-}
-    The class methods do not match:
-      The default methods associated with ‘meth’ are different.
+    • Class ‘C’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type C :: * -> Constraint
+                   class C a where
+                     meth :: a
+                     default meth :: Monoid a => a
+        Boot file: type C :: * -> Constraint
+                   class C a where
+                     meth :: a
+                     {-# MINIMAL meth #-}
+      The class methods do not match:
+        The default methods associated with ‘meth’ are different.
+    • In the class declaration for ‘C’


=====================================
testsuite/tests/typecheck/should_fail/T3468.stderr
=====================================
@@ -1,10 +1,11 @@
 
 T3468.hs-boot:3:1: error: [GHC-15843]
-    Type constructor ‘Tool’ has conflicting definitions in the module
-    and its hs-boot file.
-    Main module: type role Tool phantom
-                 type Tool :: * -> *
-                 data Tool d = forall a r. F a
-      Boot file: type Tool :: *
-                 data Tool
-    The types have different kinds.
+    • Type constructor ‘Tool’ has conflicting definitions in the module
+      and its hs-boot file.
+      Main module: type role Tool phantom
+                   type Tool :: * -> *
+                   data Tool d = forall a r. F a
+        Boot file: type Tool :: *
+                   data Tool
+      The types have different kinds.
+    • In the data type declaration for ‘Tool’



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/294e199c39e14a2e2b47b4977ae3751b694fcb9f...15fd2738302ee25be8fd821e8abfc6db510f288b

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/294e199c39e14a2e2b47b4977ae3751b694fcb9f...15fd2738302ee25be8fd821e8abfc6db510f288b
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230827/39c4ec84/attachment-0001.html>


More information about the ghc-commits mailing list