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
-
bcdec657
by Zubin Duggal at 2025-08-05T10:37:29+05:30
-
8429f85c
by Andrew Lelechenko at 2025-08-05T12:15:10-04:00
-
8b919f58
by Peng Fan at 2025-08-05T12:15:24-04:00
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:
... | ... | @@ -1972,9 +1972,17 @@ genCCall target dest_regs arg_regs = do |
1972 | 1972 | (val, fmt_val, code_val) <- getSomeReg val_reg
|
1973 | 1973 | let instrs = case ord of
|
1974 | 1974 | MemOrderRelaxed -> unitOL $ ann moDescr (ST fmt_val (OpReg w val) (OpAddr $ AddrReg p))
|
1975 | - -- implement with AMSWAPDB
|
|
1976 | - MemOrderRelease -> unitOL $ ann moDescr (AMSWAPDB fmt_val (OpReg w zeroReg) (OpReg w val) (OpReg w p))
|
|
1977 | - MemOrderSeqCst -> unitOL $ ann moDescr (AMSWAPDB fmt_val (OpReg w zeroReg) (OpReg w val) (OpReg w p))
|
|
1975 | + -- AMSWAP_DB* insns implentment a fully functional synchronization barrier, like DBAR 0x0.
|
|
1976 | + -- This is terrible. And AMSWAPDB only supports ISA version greater than LA64V1_0. So,
|
|
1977 | + -- implement with DBAR
|
|
1978 | + MemOrderRelease -> toOL [
|
|
1979 | + ann moDescr (DBAR HintRelease),
|
|
1980 | + ST fmt_val (OpReg w val) (OpAddr $ AddrReg p)
|
|
1981 | + ]
|
|
1982 | + MemOrderSeqCst -> toOL [
|
|
1983 | + ann moDescr (DBAR HintSeqcst),
|
|
1984 | + ST fmt_val (OpReg w val) (OpAddr $ AddrReg p)
|
|
1985 | + ]
|
|
1978 | 1986 | _ -> panic $ "Unexpected MemOrderAcquire on an AtomicWrite" ++ show mo
|
1979 | 1987 | moDescr = (text . show) mo
|
1980 | 1988 | code =
|
... | ... | @@ -245,7 +245,7 @@ import GHC.Types.IPE |
245 | 245 | import GHC.Types.SourceFile
|
246 | 246 | import GHC.Types.SrcLoc
|
247 | 247 | import GHC.Types.Name
|
248 | -import GHC.Types.Name.Cache ( newNameCache, knownKeysOrigNameCache )
|
|
248 | +import GHC.Types.Name.Cache ( newNameCache )
|
|
249 | 249 | import GHC.Types.Name.Reader
|
250 | 250 | import GHC.Types.Name.Ppr
|
251 | 251 | import GHC.Types.TyThing
|
... | ... | @@ -322,7 +322,7 @@ newHscEnv top_dir dflags = do |
322 | 322 | |
323 | 323 | newHscEnvWithHUG :: FilePath -> DynFlags -> UnitId -> HomeUnitGraph -> IO HscEnv
|
324 | 324 | newHscEnvWithHUG top_dir top_dynflags cur_unit home_unit_graph = do
|
325 | - nc_var <- newNameCache 'r' knownKeysOrigNameCache
|
|
325 | + nc_var <- newNameCache
|
|
326 | 326 | fc_var <- initFinderCache
|
327 | 327 | logger <- initLogger
|
328 | 328 | tmpfs <- initTmpFs
|
... | ... | @@ -4,6 +4,7 @@ |
4 | 4 | module GHC.Types.Name.Cache
|
5 | 5 | ( NameCache (..)
|
6 | 6 | , newNameCache
|
7 | + , newNameCacheWith
|
|
7 | 8 | , initNameCache
|
8 | 9 | , takeUniqFromNameCache
|
9 | 10 | , updateNameCache'
|
... | ... | @@ -140,11 +141,27 @@ extendOrigNameCache nc mod occ name |
140 | 141 | where
|
141 | 142 | combine _ occ_env = extendOccEnv occ_env occ name
|
142 | 143 | |
143 | -newNameCache :: Char -> OrigNameCache -> IO NameCache
|
|
144 | -newNameCache c nc = NameCache c <$> newMVar nc
|
|
144 | +-- | Initialize a new name cache
|
|
145 | +newNameCache :: IO NameCache
|
|
146 | +newNameCache = newNameCacheWith 'r' knownKeysOrigNameCache
|
|
145 | 147 | |
148 | +-- | This is a version of `newNameCache` that lets you supply your
|
|
149 | +-- own unique tag and set of known key names. This can go wrong if the tag
|
|
150 | +-- supplied is one reserved by GHC for internal purposes. See #26055 for
|
|
151 | +-- an example.
|
|
152 | +--
|
|
153 | +-- Use `newNameCache` when possible.
|
|
154 | +newNameCacheWith :: Char -> OrigNameCache -> IO NameCache
|
|
155 | +newNameCacheWith c nc = NameCache c <$> newMVar nc
|
|
156 | + |
|
157 | +-- | This takes a tag for uniques to be generated and the list of knownKeyNames
|
|
158 | +-- These must be initialized properly to ensure that names generated from this
|
|
159 | +-- NameCache do not conflict with known key names.
|
|
160 | +--
|
|
161 | +-- Use `newNameCache` or `newNameCacheWith` instead
|
|
162 | +{-# DEPRECATED initNameCache "Use newNameCache or newNameCacheWith instead" #-}
|
|
146 | 163 | initNameCache :: Char -> [Name] -> IO NameCache
|
147 | -initNameCache c names = newNameCache c (initOrigNames names)
|
|
164 | +initNameCache c names = newNameCacheWith c (initOrigNames names)
|
|
148 | 165 | |
149 | 166 | initOrigNames :: [Name] -> OrigNameCache
|
150 | 167 | initOrigNames names = foldl' extendOrigNameCache' emptyModuleEnv names
|
1 | -# GHC's configure script reports that GHC versions 9.6 and greater are required
|
|
1 | +# GHC's configure script reports that GHC versions 9.10 and greater are required
|
|
2 | 2 | # to build GHC from source.
|
3 | -resolver: lts-22.44 # GHC 9.6.7
|
|
3 | +resolver: lts-24.2 # GHC 9.10.2
|
|
4 | 4 | |
5 | 5 | packages:
|
6 | 6 | - '.'
|
1 | 1 | # This file was autogenerated by Stack.
|
2 | 2 | # You should not edit this file by hand.
|
3 | 3 | # For more information, please see the documentation at:
|
4 | -# https://docs.haskellstack.org/en/stable/lock_files
|
|
4 | +# https://docs.haskellstack.org/en/stable/topics/lock_files
|
|
5 | 5 | |
6 | 6 | packages:
|
7 | 7 | - completed:
|
... | ... | @@ -40,9 +40,9 @@ packages: |
40 | 40 | original:
|
41 | 41 | hackage: filepath-1.4.300.2
|
42 | 42 | - completed:
|
43 | - hackage: process-1.6.25.0@sha256:092ab61596e914d21983aa2e9206a74c4faa38a5a636446b5c954305821cb496,2749
|
|
43 | + hackage: process-1.6.25.0@sha256:9a0b2ef8096517fa0e0c7a5e9a5c2ae5744ed824c3331005f9408245810df345,2640
|
|
44 | 44 | pantry-tree:
|
45 | - sha256: bdab416d3c454ad716d4fab1ced490cc75330658c1c7c66a0b6f4b3e5125017b
|
|
45 | + sha256: 9c7927cd4d7f2f4c64251256eb6904800b3922fa5c5424c60f0e08441693e12b
|
|
46 | 46 | size: 1790
|
47 | 47 | original:
|
48 | 48 | hackage: process-1.6.25.0
|
... | ... | @@ -55,7 +55,7 @@ packages: |
55 | 55 | hackage: unix-2.8.5.1
|
56 | 56 | snapshots:
|
57 | 57 | - completed:
|
58 | - sha256: 238fa745b64f91184f9aa518fe04bdde6552533d169b0da5256670df83a0f1a9
|
|
59 | - size: 721141
|
|
60 | - url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/22/44.yaml
|
|
61 | - original: lts-22.44 |
|
58 | + sha256: cd28bd74375205718f1d5fa221730a9c17a203059708b1eb95f4b20d68bf82d9
|
|
59 | + size: 724943
|
|
60 | + url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/24/2.yaml
|
|
61 | + original: lts-24.2 |
... | ... | @@ -30,7 +30,6 @@ |
30 | 30 | * `GHC.TypeNats.Internal`
|
31 | 31 | * `GHC.ExecutionStack.Internal`.
|
32 | 32 | * Deprecate `GHC.JS.Prim.Internal.Build`, as per [CLC #329](https://github.com/haskell/core-libraries-committee/issues/329)
|
33 | - * Expose constructor and field of `Backtraces` from `Control.Exception.Backtrace`, as per [CLC #199](https://github.com/haskell/core-libraries-committee/issues/199#issuecomment-1954662391)
|
|
34 | 33 | |
35 | 34 | * 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)).
|
36 | 35 | * 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)).
|
... | ... | @@ -51,7 +51,7 @@ module Control.Exception.Backtrace |
51 | 51 | , getBacktraceMechanismState
|
52 | 52 | , setBacktraceMechanismState
|
53 | 53 | -- * Collecting backtraces
|
54 | - , Backtraces(..)
|
|
54 | + , Backtraces
|
|
55 | 55 | , displayBacktraces
|
56 | 56 | , collectBacktraces
|
57 | 57 | ) where
|
... | ... | @@ -25,9 +25,6 @@ import GHC.Iface.Ext.Utils |
25 | 25 | import GHC.Driver.Session
|
26 | 26 | import GHC.SysTools
|
27 | 27 | |
28 | -makeNc :: IO NameCache
|
|
29 | -makeNc = initNameCache 'z' []
|
|
30 | - |
|
31 | 28 | dynFlagsForPrinting :: String -> IO DynFlags
|
32 | 29 | dynFlagsForPrinting libdir = do
|
33 | 30 | systemSettings <- initSysTools libdir
|
... | ... | @@ -37,7 +34,7 @@ readTestHie :: FilePath -> IO (DynFlags, HieFile) |
37 | 34 | readTestHie fp = do
|
38 | 35 | libdir:_ <- getArgs
|
39 | 36 | df <- dynFlagsForPrinting libdir
|
40 | - nc <- makeNc
|
|
37 | + nc <- newNameCache
|
|
41 | 38 | hfr <- readHieFile nc fp
|
42 | 39 | pure (df, hie_file_result hfr)
|
43 | 40 |
... | ... | @@ -323,7 +323,7 @@ module Control.Exception.Backtrace where |
323 | 323 | type BacktraceMechanism :: *
|
324 | 324 | data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
325 | 325 | type Backtraces :: *
|
326 | - 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]}
|
|
326 | + data Backtraces = ...
|
|
327 | 327 | collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
328 | 328 | displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
329 | 329 | getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
... | ... | @@ -323,7 +323,7 @@ module Control.Exception.Backtrace where |
323 | 323 | type BacktraceMechanism :: *
|
324 | 324 | data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
325 | 325 | type Backtraces :: *
|
326 | - 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]}
|
|
326 | + data Backtraces = ...
|
|
327 | 327 | collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
328 | 328 | displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
329 | 329 | getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
... | ... | @@ -323,7 +323,7 @@ module Control.Exception.Backtrace where |
323 | 323 | type BacktraceMechanism :: *
|
324 | 324 | data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
325 | 325 | type Backtraces :: *
|
326 | - 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]}
|
|
326 | + data Backtraces = ...
|
|
327 | 327 | collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
328 | 328 | displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
329 | 329 | getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
... | ... | @@ -323,7 +323,7 @@ module Control.Exception.Backtrace where |
323 | 323 | type BacktraceMechanism :: *
|
324 | 324 | data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
325 | 325 | type Backtraces :: *
|
326 | - 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]}
|
|
326 | + data Backtraces = ...
|
|
327 | 327 | collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
328 | 328 | displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
329 | 329 | getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|