Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
-
0491f08a
by Sylvain Henry at 2026-01-22T03:44:26-05:00
-
211a8f56
by Sylvain Henry at 2026-01-22T03:44:26-05:00
-
77a23cbd
by fendor at 2026-01-22T03:45:08-05:00
-
7bc0a3f6
by Léana Jiang at 2026-01-22T04:18:13-05:00
-
385ff864
by Cheng Shao at 2026-01-22T04:18:14-05:00
-
285c2c47
by Matthew Pickering at 2026-01-22T04:18:15-05:00
-
ba24973b
by Zubin Duggal at 2026-01-22T04:18:16-05:00
12 changed files:
- .gitignore
- hadrian/doc/user-settings.md
- hadrian/src/Rules/Documentation.hs
- hadrian/src/Settings/Packages.hs
- libraries/ghc-experimental/ghc-experimental.cabal.in
- libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs
- rts/rts.cabal
- rts/sm/Evac.c
- rts/sm/Evac_thr.c → rts/sm/Evac_par.c
- rts/sm/Scav_thr.c → rts/sm/Scav_par.c
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
Changes:
| ... | ... | @@ -261,7 +261,7 @@ dist-newstyle/ |
| 261 | 261 | # CI
|
| 262 | 262 | |
| 263 | 263 | # Windows CI
|
| 264 | -toolchain/
|
|
| 265 | -ghc-*/
|
|
| 266 | -inplace/
|
|
| 267 | -tmp/ |
|
| 264 | +/toolchain/
|
|
| 265 | +/ghc-*/
|
|
| 266 | +/inplace/
|
|
| 267 | +/tmp/ |
| ... | ... | @@ -19,14 +19,18 @@ A build _flavour_ is a collection of build settings that fully define a GHC buil |
| 19 | 19 | data Flavour = Flavour {
|
| 20 | 20 | -- | Flavour name, to select this flavour from command line.
|
| 21 | 21 | name :: String,
|
| 22 | - -- | Use these command line arguments.
|
|
| 23 | - args :: Args,
|
|
| 22 | + -- | Use these extra command line arguments.
|
|
| 23 | + -- This can't depend on the result of configuring a package (ie, using readContextData)
|
|
| 24 | + extraArgs :: Args,
|
|
| 24 | 25 | -- | Build these packages.
|
| 25 | 26 | packages :: Stage -> Action [Package],
|
| 26 | 27 | -- | Bignum backend: 'native', 'gmp', 'ffi', etc.
|
| 27 | 28 | bignumBackend :: String,
|
| 28 | 29 | -- | Check selected bignum backend against native backend
|
| 29 | 30 | bignumCheck :: Bool,
|
| 31 | + -- | Build the @text@ package with @simdutf@ support. Disabled by
|
|
| 32 | + -- default due to packaging difficulties described in #20724.
|
|
| 33 | + textWithSIMDUTF :: Bool,
|
|
| 30 | 34 | -- | Build libraries these ways.
|
| 31 | 35 | libraryWays :: Ways,
|
| 32 | 36 | -- | Build RTS these ways.
|
| ... | ... | @@ -45,11 +49,18 @@ data Flavour = Flavour { |
| 45 | 49 | -- | Build the GHC executable against the threaded runtime system.
|
| 46 | 50 | ghcThreaded :: Stage -- ^ stage of the /built/ compiler
|
| 47 | 51 | -> Bool,
|
| 52 | + |
|
| 53 | + ghcSplitSections :: Bool, -- ^ Whether to enable split sections
|
|
| 48 | 54 | -- | Whether to build docs and which ones
|
| 49 | 55 | -- (haddocks, user manual, haddock manual)
|
| 50 | 56 | ghcDocs :: Action DocTargets,
|
| 57 | + |
|
| 58 | + -- | Whether to uses hashes or inplace for unit ids
|
|
| 59 | + hashUnitIds :: Bool,
|
|
| 60 | + |
|
| 51 | 61 | -- | Whether to generate .hie files
|
| 52 | 62 | ghcHieFiles :: Stage -> Bool
|
| 63 | + |
|
| 53 | 64 | }
|
| 54 | 65 | ```
|
| 55 | 66 | Hadrian provides several built-in flavours (`default`, `quick`, and a few
|
| ... | ... | @@ -74,6 +74,8 @@ needDocDeps = do |
| 74 | 74 | let templatedCabalFiles = map pkgCabalFile
|
| 75 | 75 | [ ghcBoot
|
| 76 | 76 | , ghcBootTh
|
| 77 | + , ghcExperimental
|
|
| 78 | + , ghcInternal
|
|
| 77 | 79 | , ghci
|
| 78 | 80 | , compiler
|
| 79 | 81 | , ghcHeap
|
| ... | ... | @@ -53,7 +53,7 @@ packageArgs = do |
| 53 | 53 | -- for Stage0 only so we can link ghc-pkg against it, so there is little
|
| 54 | 54 | -- reason to spend the effort to optimise it.
|
| 55 | 55 | , package cabal ?
|
| 56 | - stage0 ? builder Ghc ? arg "-O0"
|
|
| 56 | + andM [stage0, notCross] ? builder Ghc ? arg "-O0"
|
|
| 57 | 57 | |
| 58 | 58 | ------------------------------- compiler -------------------------------
|
| 59 | 59 | , package compiler ? mconcat
|
| ... | ... | @@ -71,7 +71,7 @@ packageArgs = do |
| 71 | 71 | -- These files take a very long time to compile with -O1,
|
| 72 | 72 | -- so we use -O0 for them just in Stage0 to speed up the
|
| 73 | 73 | -- build but not affect Stage1+ executables
|
| 74 | - , inputs ["**/GHC/Hs/Instances.hs", "**/GHC/Driver/Session.hs"] ? stage0 ?
|
|
| 74 | + , inputs ["**/GHC/Hs/Instances.hs", "**/GHC/Driver/Session.hs"] ? andM [stage0, notCross] ?
|
|
| 75 | 75 | pure ["-O0"] ]
|
| 76 | 76 | |
| 77 | 77 | , builder (Cabal Setup) ? mconcat
|
| ... | ... | @@ -44,6 +44,7 @@ library |
| 44 | 44 | GHC.Stats.Experimental
|
| 45 | 45 | Prelude.Experimental
|
| 46 | 46 | System.Mem.Experimental
|
| 47 | + GHC.Exception.Backtrace.Experimental
|
|
| 47 | 48 | if arch(wasm32)
|
| 48 | 49 | exposed-modules: GHC.Wasm.Prim
|
| 49 | 50 | other-extensions:
|
| ... | ... | @@ -15,7 +15,7 @@ module GHC.Exception.Backtrace.Experimental |
| 15 | 15 | , getBacktraceMechanismState
|
| 16 | 16 | , setBacktraceMechanismState
|
| 17 | 17 | -- * Collecting backtraces
|
| 18 | - , Backtraces(..),
|
|
| 18 | + , Backtraces(..)
|
|
| 19 | 19 | , displayBacktraces
|
| 20 | 20 | , collectBacktraces
|
| 21 | 21 | -- * Collecting exception annotations on throwing 'Exception's
|
| ... | ... | @@ -511,7 +511,7 @@ library |
| 511 | 511 | sm/CNF.c
|
| 512 | 512 | sm/Compact.c
|
| 513 | 513 | sm/Evac.c
|
| 514 | - sm/Evac_thr.c
|
|
| 514 | + sm/Evac_par.c
|
|
| 515 | 515 | sm/GC.c
|
| 516 | 516 | sm/GCAux.c
|
| 517 | 517 | sm/GCUtils.c
|
| ... | ... | @@ -526,7 +526,7 @@ library |
| 526 | 526 | sm/NonMovingSweep.c
|
| 527 | 527 | sm/Sanity.c
|
| 528 | 528 | sm/Scav.c
|
| 529 | - sm/Scav_thr.c
|
|
| 529 | + sm/Scav_par.c
|
|
| 530 | 530 | sm/Storage.c
|
| 531 | 531 | sm/Sweep.c
|
| 532 | 532 | fs.c
|
| ... | ... | @@ -498,7 +498,7 @@ evacuate_static_object (StgClosure **link_field, StgClosure *q) |
| 498 | 498 | // See Note [STATIC_LINK fields] for how the link field bits work
|
| 499 | 499 | if (((link & STATIC_BITS) | prev_static_flag) != 3) {
|
| 500 | 500 | StgWord new_list_head = (StgWord)q | static_flag;
|
| 501 | -#if !defined(THREADED_RTS)
|
|
| 501 | +#if !defined(PARALLEL_GC)
|
|
| 502 | 502 | *link_field = gct->static_objects;
|
| 503 | 503 | gct->static_objects = (StgClosure *)new_list_head;
|
| 504 | 504 | #else
|
| ... | ... | @@ -4454,6 +4454,22 @@ module Data.Tuple.Experimental where |
| 4454 | 4454 | data Unit# = ...
|
| 4455 | 4455 | getSolo :: forall a. Solo a -> a
|
| 4456 | 4456 | |
| 4457 | +module GHC.Exception.Backtrace.Experimental where
|
|
| 4458 | + -- Safety: None
|
|
| 4459 | + type BacktraceMechanism :: *
|
|
| 4460 | + data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
|
| 4461 | + type Backtraces :: *
|
|
| 4462 | + 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.StackTrace, btrIpe :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.CloneStack.StackSnapshot}
|
|
| 4463 | + type CollectExceptionAnnotationMechanism :: *
|
|
| 4464 | + data CollectExceptionAnnotationMechanism = ...
|
|
| 4465 | + collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
|
| 4466 | + collectExceptionAnnotation :: GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Types.IO GHC.Internal.Exception.Context.SomeExceptionAnnotation
|
|
| 4467 | + displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
|
| 4468 | + getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
|
| 4469 | + getCollectExceptionAnnotationMechanism :: GHC.Internal.Types.IO CollectExceptionAnnotationMechanism
|
|
| 4470 | + setBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.Bool -> GHC.Internal.Types.IO ()
|
|
| 4471 | + setCollectExceptionAnnotation :: forall a. GHC.Internal.Exception.Context.ExceptionAnnotation a => (GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Types.IO a) -> GHC.Internal.Types.IO ()
|
|
| 4472 | + |
|
| 4457 | 4473 | module GHC.PrimOps where
|
| 4458 | 4474 | -- Safety: Unsafe
|
| 4459 | 4475 | (*#) :: Int# -> Int# -> Int#
|
| ... | ... | @@ -11182,6 +11198,7 @@ instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘ |
| 11182 | 11198 | instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
|
| 11183 | 11199 | instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
|
| 11184 | 11200 | instance GHC.Internal.Enum.Enum GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
|
| 11201 | +instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Backtrace.Backtraces -- Defined in ‘GHC.Internal.Exception.Backtrace’
|
|
| 11185 | 11202 | instance forall a. GHC.Internal.Float.Floating a => GHC.Internal.Float.Floating (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| 11186 | 11203 | instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Float.RealFloat (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| 11187 | 11204 | instance forall a. GHC.Internal.Foreign.Storable.Storable a => GHC.Internal.Foreign.Storable.Storable (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| ... | ... | @@ -4454,6 +4454,22 @@ module Data.Tuple.Experimental where |
| 4454 | 4454 | data Unit# = ...
|
| 4455 | 4455 | getSolo :: forall a. Solo a -> a
|
| 4456 | 4456 | |
| 4457 | +module GHC.Exception.Backtrace.Experimental where
|
|
| 4458 | + -- Safety: None
|
|
| 4459 | + type BacktraceMechanism :: *
|
|
| 4460 | + data BacktraceMechanism = CostCentreBacktrace | HasCallStackBacktrace | ExecutionBacktrace | IPEBacktrace
|
|
| 4461 | + type Backtraces :: *
|
|
| 4462 | + 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.StackTrace, btrIpe :: GHC.Internal.Maybe.Maybe GHC.Internal.Stack.CloneStack.StackSnapshot}
|
|
| 4463 | + type CollectExceptionAnnotationMechanism :: *
|
|
| 4464 | + data CollectExceptionAnnotationMechanism = ...
|
|
| 4465 | + collectBacktraces :: (?callStack::GHC.Internal.Stack.Types.CallStack) => GHC.Internal.Types.IO Backtraces
|
|
| 4466 | + collectExceptionAnnotation :: GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Types.IO GHC.Internal.Exception.Context.SomeExceptionAnnotation
|
|
| 4467 | + displayBacktraces :: Backtraces -> GHC.Internal.Base.String
|
|
| 4468 | + getBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.IO GHC.Internal.Types.Bool
|
|
| 4469 | + getCollectExceptionAnnotationMechanism :: GHC.Internal.Types.IO CollectExceptionAnnotationMechanism
|
|
| 4470 | + setBacktraceMechanismState :: BacktraceMechanism -> GHC.Internal.Types.Bool -> GHC.Internal.Types.IO ()
|
|
| 4471 | + setCollectExceptionAnnotation :: forall a. GHC.Internal.Exception.Context.ExceptionAnnotation a => (GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Types.IO a) -> GHC.Internal.Types.IO ()
|
|
| 4472 | + |
|
| 4457 | 4473 | module GHC.PrimOps where
|
| 4458 | 4474 | -- Safety: Unsafe
|
| 4459 | 4475 | (*#) :: Int# -> Int# -> Int#
|
| ... | ... | @@ -11185,6 +11201,7 @@ instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘ |
| 11185 | 11201 | instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
|
| 11186 | 11202 | instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
|
| 11187 | 11203 | instance GHC.Internal.Enum.Enum GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
|
| 11204 | +instance GHC.Internal.Exception.Context.ExceptionAnnotation GHC.Internal.Exception.Backtrace.Backtraces -- Defined in ‘GHC.Internal.Exception.Backtrace’
|
|
| 11188 | 11205 | instance forall a. GHC.Internal.Float.Floating a => GHC.Internal.Float.Floating (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| 11189 | 11206 | instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Float.RealFloat (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|
| 11190 | 11207 | instance forall a. GHC.Internal.Foreign.Storable.Storable a => GHC.Internal.Foreign.Storable.Storable (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
|