Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
4f6bc9cf by fendor at 2025-08-04T17:50:06-04:00
Revert "base: Expose Backtraces constructor and fields"
This reverts commit 17db44c5b32fff82ea988fa4f1a233d1a27bdf57.
- - - - -
bcdec657 by Zubin Duggal at 2025-08-05T10:37:29+05:30
compiler: Export a version of `newNameCache` that is not prone to footguns.
`newNameCache` must be initialized with both a non-"reserved" unique tag, as well
as a list of known key names. Failing to do so results in hard to debug unique conflicts.
It is difficult for API users to tell which unique tags are safe to use. So instead of leaving
this up to the user to decide, we now export a version of `newNameCache` which uses a guaranteed
non-reserved unique tag. In fact, this is now the way the unique tag is initialized for all invocations
of the compiler.
The original version of `newNameCache` is now exported as `newNameCache'` for advanced users.
We also deprecate `initNameCache` as it is also prone to footguns and is completely subsumed in
functionality by `newNameCache` and `newNameCache'`.
Fixes #26135 and #26055
- - - - -
8429f85c by Andrew Lelechenko at 2025-08-05T12:15:10-04:00
hadrian: bump Stackage snapshot to LTS 24.2 / GHC 9.10.2
In line with #25693 we should use GHC 9.10 as a boot compiler,
while Hadrian stack.yaml was stuck on GHC 9.6.
- - - - -
8b919f58 by Peng Fan at 2025-08-05T12:15:24-04:00
NCG/LA64: implement atomic write with finer-grained DBAR hints
Signed-off-by: Peng Fan
- - - - -
12 changed files:
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Types/Name/Cache.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- testsuite/tests/hiefile/should_run/TestUtils.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
Changes:
=====================================
compiler/GHC/CmmToAsm/LA64/CodeGen.hs
=====================================
@@ -1972,9 +1972,17 @@ genCCall target dest_regs arg_regs = do
(val, fmt_val, code_val) <- getSomeReg val_reg
let instrs = case ord of
MemOrderRelaxed -> unitOL $ ann moDescr (ST fmt_val (OpReg w val) (OpAddr $ AddrReg p))
- -- implement with AMSWAPDB
- MemOrderRelease -> unitOL $ ann moDescr (AMSWAPDB fmt_val (OpReg w zeroReg) (OpReg w val) (OpReg w p))
- MemOrderSeqCst -> unitOL $ ann moDescr (AMSWAPDB fmt_val (OpReg w zeroReg) (OpReg w val) (OpReg w p))
+ -- AMSWAP_DB* insns implentment a fully functional synchronization barrier, like DBAR 0x0.
+ -- This is terrible. And AMSWAPDB only supports ISA version greater than LA64V1_0. So,
+ -- implement with DBAR
+ MemOrderRelease -> toOL [
+ ann moDescr (DBAR HintRelease),
+ ST fmt_val (OpReg w val) (OpAddr $ AddrReg p)
+ ]
+ MemOrderSeqCst -> toOL [
+ ann moDescr (DBAR HintSeqcst),
+ ST fmt_val (OpReg w val) (OpAddr $ AddrReg p)
+ ]
_ -> panic $ "Unexpected MemOrderAcquire on an AtomicWrite" ++ show mo
moDescr = (text . show) mo
code =
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -245,7 +245,7 @@ import GHC.Types.IPE
import GHC.Types.SourceFile
import GHC.Types.SrcLoc
import GHC.Types.Name
-import GHC.Types.Name.Cache ( newNameCache, knownKeysOrigNameCache )
+import GHC.Types.Name.Cache ( newNameCache )
import GHC.Types.Name.Reader
import GHC.Types.Name.Ppr
import GHC.Types.TyThing
@@ -322,7 +322,7 @@ newHscEnv top_dir dflags = do
newHscEnvWithHUG :: FilePath -> DynFlags -> UnitId -> HomeUnitGraph -> IO HscEnv
newHscEnvWithHUG top_dir top_dynflags cur_unit home_unit_graph = do
- nc_var <- newNameCache 'r' knownKeysOrigNameCache
+ nc_var <- newNameCache
fc_var <- initFinderCache
logger <- initLogger
tmpfs <- initTmpFs
=====================================
compiler/GHC/Types/Name/Cache.hs
=====================================
@@ -4,6 +4,7 @@
module GHC.Types.Name.Cache
( NameCache (..)
, newNameCache
+ , newNameCacheWith
, initNameCache
, takeUniqFromNameCache
, updateNameCache'
@@ -140,11 +141,27 @@ extendOrigNameCache nc mod occ name
where
combine _ occ_env = extendOccEnv occ_env occ name
-newNameCache :: Char -> OrigNameCache -> IO NameCache
-newNameCache c nc = NameCache c <$> newMVar nc
+-- | Initialize a new name cache
+newNameCache :: IO NameCache
+newNameCache = newNameCacheWith 'r' knownKeysOrigNameCache
+-- | This is a version of `newNameCache` that lets you supply your
+-- own unique tag and set of known key names. This can go wrong if the tag
+-- supplied is one reserved by GHC for internal purposes. See #26055 for
+-- an example.
+--
+-- Use `newNameCache` when possible.
+newNameCacheWith :: Char -> OrigNameCache -> IO NameCache
+newNameCacheWith c nc = NameCache c <$> newMVar nc
+
+-- | This takes a tag for uniques to be generated and the list of knownKeyNames
+-- These must be initialized properly to ensure that names generated from this
+-- NameCache do not conflict with known key names.
+--
+-- Use `newNameCache` or `newNameCacheWith` instead
+{-# DEPRECATED initNameCache "Use newNameCache or newNameCacheWith instead" #-}
initNameCache :: Char -> [Name] -> IO NameCache
-initNameCache c names = newNameCache c (initOrigNames names)
+initNameCache c names = newNameCacheWith c (initOrigNames names)
initOrigNames :: [Name] -> OrigNameCache
initOrigNames names = foldl' extendOrigNameCache' emptyModuleEnv names
=====================================
hadrian/stack.yaml
=====================================
@@ -1,6 +1,6 @@
-# GHC's configure script reports that GHC versions 9.6 and greater are required
+# GHC's configure script reports that GHC versions 9.10 and greater are required
# to build GHC from source.
-resolver: lts-22.44 # GHC 9.6.7
+resolver: lts-24.2 # GHC 9.10.2
packages:
- '.'
=====================================
hadrian/stack.yaml.lock
=====================================
@@ -1,7 +1,7 @@
# This file was autogenerated by Stack.
# You should not edit this file by hand.
# For more information, please see the documentation at:
-# https://docs.haskellstack.org/en/stable/lock_files
+# https://docs.haskellstack.org/en/stable/topics/lock_files
packages:
- completed:
@@ -40,9 +40,9 @@ packages:
original:
hackage: filepath-1.4.300.2
- completed:
- hackage: process-1.6.25.0@sha256:092ab61596e914d21983aa2e9206a74c4faa38a5a636446b5c954305821cb496,2749
+ hackage: process-1.6.25.0@sha256:9a0b2ef8096517fa0e0c7a5e9a5c2ae5744ed824c3331005f9408245810df345,2640
pantry-tree:
- sha256: bdab416d3c454ad716d4fab1ced490cc75330658c1c7c66a0b6f4b3e5125017b
+ sha256: 9c7927cd4d7f2f4c64251256eb6904800b3922fa5c5424c60f0e08441693e12b
size: 1790
original:
hackage: process-1.6.25.0
@@ -55,7 +55,7 @@ packages:
hackage: unix-2.8.5.1
snapshots:
- completed:
- sha256: 238fa745b64f91184f9aa518fe04bdde6552533d169b0da5256670df83a0f1a9
- size: 721141
- url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/maste...
- original: lts-22.44
+ sha256: cd28bd74375205718f1d5fa221730a9c17a203059708b1eb95f4b20d68bf82d9
+ size: 724943
+ url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/maste...
+ original: lts-24.2
=====================================
libraries/base/changelog.md
=====================================
@@ -30,7 +30,6 @@
* `GHC.TypeNats.Internal`
* `GHC.ExecutionStack.Internal`.
* Deprecate `GHC.JS.Prim.Internal.Build`, as per [CLC #329](https://github.com/haskell/core-libraries-committee/issues/329)
- * Expose constructor and field of `Backtraces` from `Control.Exception.Backtrace`, as per [CLC #199](https://github.com/haskell/core-libraries-committee/issues/199#issuecomment-...)
* Fix incorrect results of `integerPowMod` when the base is 0 and the exponent is negative, and `integerRecipMod` when the modulus is zero ([#26017](https://gitlab.haskell.org/ghc/ghc/-/issues/26017)).
* Fix the rewrite rule for `scanl'` not being strict in the first element of the output list ([#26143](https://gitlab.haskell.org/ghc/ghc/-/issues/26143)).
=====================================
libraries/base/src/Control/Exception/Backtrace.hs
=====================================
@@ -51,7 +51,7 @@ module Control.Exception.Backtrace
, getBacktraceMechanismState
, setBacktraceMechanismState
-- * Collecting backtraces
- , Backtraces(..)
+ , Backtraces
, displayBacktraces
, collectBacktraces
) where
=====================================
testsuite/tests/hiefile/should_run/TestUtils.hs
=====================================
@@ -25,9 +25,6 @@ import GHC.Iface.Ext.Utils
import GHC.Driver.Session
import GHC.SysTools
-makeNc :: IO NameCache
-makeNc = initNameCache 'z' []
-
dynFlagsForPrinting :: String -> IO DynFlags
dynFlagsForPrinting libdir = do
systemSettings <- initSysTools libdir
@@ -37,7 +34,7 @@ readTestHie :: FilePath -> IO (DynFlags, HieFile)
readTestHie fp = do
libdir:_ <- getArgs
df <- dynFlagsForPrinting libdir
- nc <- makeNc
+ nc <- newNameCache
hfr <- readHieFile nc fp
pure (df, hie_file_result hfr)
=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -323,7 +323,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
+ data Backtraces = ...
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -323,7 +323,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
+ data Backtraces = ...
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -323,7 +323,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
+ data Backtraces = ...
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -323,7 +323,7 @@ module Control.Exception.Backtrace where
type BacktraceMechanism :: *
data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
type Backtraces :: *
- data Backtraces = Backtraces {btrCostCentre :: GHC.Internal.Maybe.Maybe (GHC.Internal.Ptr.Ptr GHC.Internal.Stack.CCS.CostCentreStack), btrHasCallStack :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.Types.CallStack, btrExecutionStack :: GHC.Internal.Maybe.Maybe [GHC.Internal.ExecutionStack.Internal.Location], btrIpe :: GHC.Internal.Maybe.Maybe [GHC.Internal.Stack.CloneStack.StackEntry]}
+ data Backtraces = ...
collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
displayBacktraces :: Backtraces -> GHC.Internal.Base.String
getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6eb6065c6cf2fc6d329c711f7cb70e4...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6eb6065c6cf2fc6d329c711f7cb70e4...
You're receiving this email because of your account on gitlab.haskell.org.