[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Clarify INLINE unfolding optimization docs.

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Nov 26 13:57:23 UTC 2024



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
fcc3ae6e by Andreas Klebinger at 2024-11-26T08:24:58-05:00
Clarify INLINE unfolding optimization docs.

Fixes #24660

- - - - -
88c4fe1d by Cheng Shao at 2024-11-26T08:25:34-05:00
rts: remove -Wl,-U,___darwin_check_fd_set_overflow hack

This patch bumps macOS minimum SDK version to 11.0 for x86_64-darwin
to align it with aarch64-darwin. This allows us to get rid of the
horrible -Wl,-U,___darwin_check_fd_set_overflow hack, which is causing
linker warnings and testsuite failures on macOS 15. Fixes #25504.

- - - - -
5e0649cb by doyougnu at 2024-11-26T08:57:03-05:00
ghc-experimental: expose GHC.RTS.Flags, GHC.Stats

See this CLC proposal:

- https://github.com/haskell/core-libraries-committee/issues/289

and this CLC proposal for background:

- https://github.com/haskell/core-libraries-committee/issues/288

Metric Decrease:
    MultiLayerModulesTH_OneShot

- - - - -
8522f16f by Wang Xin at 2024-11-26T08:57:08-05:00
Add -mcmodel=medium moduleflag to generated LLVM IR on LoongArch platform

With the Medium code model, the jump range of the generated jump
instruction is larger than that of the Small code model. It's a
temporary fix of the problem descriped in https://gitlab.haskell
.org/ghc/ghc/-/issues/25495. This commit requires that the LLVM
used contains the code of commit 9dd1d451d9719aa91b3bdd59c0c6679
83e1baf05, i.e., version 8.0 and later. Actually we should not
rely on LLVM, so the only way to solve this problem is to implement
the LoongArch backend.

Add new type for codemodel

- - - - -


11 changed files:

- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/CmmToLlvm.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/pragmas.rst
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/RTS/Flags/Experimental.hs
- + libraries/ghc-experimental/src/GHC/Stats/Experimental.hs
- rts/rts.cabal
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32


Changes:

=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -444,7 +444,7 @@ opsysVariables AArch64 (Darwin {}) =
           ]
 opsysVariables Amd64 (Darwin {}) =
   mconcat [ "NIX_SYSTEM" =: "x86_64-darwin"
-          , "MACOSX_DEPLOYMENT_TARGET" =: "10.13"
+          , "MACOSX_DEPLOYMENT_TARGET" =: "11.0"
           -- "# Only Sierra and onwards supports clock_gettime. See #12858"
           , "ac_cv_func_clock_gettime" =: "no"
           -- # Only newer OS Xs support utimensat. See #17895


=====================================
.gitlab/jobs.yaml
=====================================
@@ -1072,7 +1072,7 @@
       "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "LANG": "en_US.UTF-8",
-      "MACOSX_DEPLOYMENT_TARGET": "10.13",
+      "MACOSX_DEPLOYMENT_TARGET": "11.0",
       "NIX_SYSTEM": "x86_64-darwin",
       "RUNTEST_ARGS": "",
       "TEST_ENV": "x86_64-darwin-validate",
@@ -3834,7 +3834,7 @@
       "IGNORE_PERF_FAILURES": "all",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "LANG": "en_US.UTF-8",
-      "MACOSX_DEPLOYMENT_TARGET": "10.13",
+      "MACOSX_DEPLOYMENT_TARGET": "11.0",
       "NIX_SYSTEM": "x86_64-darwin",
       "RUNTEST_ARGS": "",
       "TEST_ENV": "x86_64-darwin-release",
@@ -5213,7 +5213,7 @@
       "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
       "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
       "LANG": "en_US.UTF-8",
-      "MACOSX_DEPLOYMENT_TARGET": "10.13",
+      "MACOSX_DEPLOYMENT_TARGET": "11.0",
       "NIX_SYSTEM": "x86_64-darwin",
       "RUNTEST_ARGS": "",
       "TEST_ENV": "x86_64-darwin-validate",


=====================================
compiler/GHC/CmmToLlvm.hs
=====================================
@@ -221,7 +221,12 @@ cmmMetaLlvmPrelude = do
           case platformArch platform of
             ArchX86_64 | llvmCgAvxEnabled cfg -> [mkStackAlignmentMeta 32]
             _                                 -> []
-  module_flags_metas <- mkModuleFlagsMeta stack_alignment_metas
+  let codel_model_metas =
+          case platformArch platform of
+            -- FIXME: We should not rely on LLVM
+            ArchLoongArch64 -> [mkCodeModelMeta CMMedium]
+            _                                 -> []
+  module_flags_metas <- mkModuleFlagsMeta (stack_alignment_metas ++ codel_model_metas)
   let metas = tbaa_metas ++ module_flags_metas
   cfg <- getConfig
   renderLlvm (ppLlvmMetas cfg metas)
@@ -244,6 +249,15 @@ mkStackAlignmentMeta :: Integer -> ModuleFlag
 mkStackAlignmentMeta alignment =
     ModuleFlag MFBError "override-stack-alignment" (MetaLit $ LMIntLit alignment i32)
 
+-- LLVM's @LLVM::CodeModel::Model@ enumeration
+data CodeModel = CMMedium
+
+-- Pass -mcmodel=medium option to LLVM on LoongArch64
+mkCodeModelMeta :: CodeModel -> ModuleFlag
+mkCodeModelMeta codemodel =
+    ModuleFlag MFBError "Code Model" (MetaLit $ LMIntLit n i32)
+  where
+    n = case codemodel of CMMedium -> 3 -- as of LLVM 8
 
 -- -----------------------------------------------------------------------------
 -- | Marks variables as used where necessary


=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -58,6 +58,16 @@ Cmm
 ``ghc-experimental`` library
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 
+- ``ghc-experimental`` now exposes ``GHC.RTS.Flags`` and ``GHC.Stats`` as
+  ``GHC.RTS.Flags.Experimental`` and ``GHC.Stats.Experimental``. These are
+  *also* exposed in ``base``, however the ``base`` versions will be deprecated as
+  part of the split base project. See `CLC proposal 289
+  <https://github.com/haskell/core-libraries-committee/issues/289>`__.
+  Downstream consumers of these flags are encouraged to migrate to the
+  ``ghc-experimental`` versions.
+
+
+
 ``template-haskell`` library
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 


=====================================
docs/users_guide/exts/pragmas.rst
=====================================
@@ -393,12 +393,15 @@ has a number of other effects:
    pragmas is to expose functions in ``f``\'s RHS that have rewrite
    rules, and it's no good if those functions have been optimised away.
 
-   So *GHC guarantees to inline precisely the code that you wrote*, no
-   more and no less. It does this by capturing a copy of the definition
+   So *GHC guarantees to behave precisely as if it inlined the code that you wrote*.
+   It does this by capturing a copy of the definition
    of the function to use for inlining (we call this the "inline-RHS"),
-   which it leaves untouched, while optimising the ordinarily RHS as
-   usual. For externally-visible functions the inline-RHS (not the
-   optimised RHS) is recorded in the interface file.
+   which it only optimizes in ways which don't break this promise.
+   For example if inlining is explicitly delayed through phase control GHC will
+   apply optimizations which happen before the ``INLINE`` pragma becomes
+   active to the inline-RHS while optimising the ordinarily RHS as usual.
+   For externally-visible functions
+   the inline-RHS (not the optimised RHS) is recorded in the interface file.
 
 -  An ``INLINE`` function is not worker/wrappered by strictness analysis.
    It's going to be inlined wholesale instead.


=====================================
libraries/ghc-experimental/ghc-experimental.cabal.in
=====================================
@@ -35,6 +35,8 @@ library
       GHC.Profiling.Eras
       GHC.TypeLits.Experimental
       GHC.TypeNats.Experimental
+      GHC.RTS.Flags.Experimental
+      GHC.Stats.Experimental
       Prelude.Experimental
     if arch(wasm32)
         exposed-modules:  GHC.Wasm.Prim


=====================================
libraries/ghc-experimental/src/GHC/RTS/Flags/Experimental.hs
=====================================
@@ -0,0 +1,54 @@
+-- |
+-- Module      :  GHC.RTS.Flags.Experimental
+-- Copyright   :  (c) The University of Glasgow, 1994-2000
+-- License     :  see libraries/ghc-experimental/LICENSE
+--
+-- Maintainer  :  ghc-devs at haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC extensions)
+--
+-- /The API of this module is unstable and is coupled to GHC's internals./ As
+-- such if you depend on it, you should expect to follow GHC's releases. This
+-- API could change without warning.
+--
+-- Descriptions of flags can be seen in
+-- <https://www.haskell.org/ghc/docs/latest/html/users_guide/runtime_control.html GHC User's Guide>,
+-- or by running RTS help message using @+RTS --help at .
+--
+--
+
+module GHC.RTS.Flags.Experimental
+  ( RtsTime
+  , RTSFlags (..)
+  , GiveGCStats (..)
+  , GCFlags (..)
+  , ConcFlags (..)
+  , MiscFlags (..)
+  , IoManagerFlag (..)
+  , DebugFlags (..)
+  , DoCostCentres (..)
+  , CCFlags (..)
+  , DoHeapProfile (..)
+  , ProfFlags (..)
+  , DoTrace (..)
+  , TraceFlags (..)
+  , TickyFlags (..)
+  , ParFlags (..)
+  , HpcFlags (..)
+  , {-# DEPRECATED "import GHC.IO.SubSystem (IoSubSystem (..))" #-}
+    IoSubSystem (..)
+  , getRTSFlags
+  , getGCFlags
+  , getConcFlags
+  , getMiscFlags
+  , getDebugFlags
+  , getCCFlags
+  , getProfFlags
+  , getTraceFlags
+  , getTickyFlags
+  , getParFlags
+  , getHpcFlags
+  ) where
+
+import GHC.Internal.RTS.Flags
+import GHC.Internal.IO.SubSystem (IoSubSystem(..))


=====================================
libraries/ghc-experimental/src/GHC/Stats/Experimental.hs
=====================================
@@ -0,0 +1,27 @@
+{-# LANGUAGE Safe #-}
+
+-- |
+-- Module      :  RTS.Stats.Experimental
+-- Copyright   :  (c) The University of Glasgow, 1994-2000
+-- License     :  see libraries/ghc-experimental/LICENSE
+--
+-- Maintainer  :  ghc-devs at haskell.org
+-- Stability   :  internal
+-- Portability :  non-portable (GHC extensions)
+--
+-- This module provides access to internal garbage collection and
+-- memory usage statistics.  These statistics are not available unless
+-- a program is run with the @-T@ RTS flag.
+--
+-- /The API of this module is unstable and is coupled to GHC's internals./ As
+-- such if you depend on it, you should expect to follow GHC's releases. This
+-- API could change without warning.
+
+module GHC.Stats.Experimental
+    ( -- * Runtime statistics
+      RTSStats(..), GCDetails(..), RtsTime
+    , getRTSStats
+    , getRTSStatsEnabled
+    ) where
+
+import GHC.Internal.Stats


=====================================
rts/rts.cabal
=====================================
@@ -332,8 +332,6 @@ library
 
       if os(osx)
         ld-options: "-Wl,-search_paths_first"
-                    -- See Note [fd_set_overflow]
-                    "-Wl,-U,___darwin_check_fd_set_overflow"
                     -- See Note [Undefined symbols in the RTS]
                     "-Wl,-undefined,dynamic_lookup"
         if !arch(x86_64) && !arch(aarch64)
@@ -549,48 +547,6 @@ library
                     -- We don't want to compile posix/ticker/*.c, these will be #included
                     -- from Ticker.c
 
-
--- Note [fd_set_overflow]
--- ~~~~~~~~~~~~~~~~~~~~~~
--- In this note is the very sad tale of __darwin_fd_set_overflow.
--- The 8.10.5 release was broken because it was built in an environment
--- where the libraries were provided by XCode 12.*, these libraries introduced
--- a reference to __darwin_fd_set_overflow via the FD_SET macro which is used in
--- Select.c. Unfortunately, this symbol is not available with XCode 11.* which
--- led to a linker error when trying to link anything. This is almost certainly
--- a bug in XCode but we still have to work around it.
-
--- Undefined symbols for architecture x86_64:
---  "___darwin_check_fd_set_overflow", referenced from:
---      _awaitEvent in libHSrts.a(Select.o)
--- ld: symbol(s) not found for architecture x86_64
-
--- One way to fix this is to upgrade your version of xcode, but this would
--- force the upgrade on users prematurely. Fortunately it also seems safe to pass
--- the linker option "-Wl,-U,___darwin_check_fd_set_overflow" because the usage of
--- the symbol is guarded by a guard to check if it's defined.
-
--- __header_always_inline int
--- __darwin_check_fd_set(int _a, const void *_b)
--- {
---    if ((uintptr_t)&__darwin_check_fd_set_overflow != (uintptr_t) 0) {
---#if defined(_DARWIN_UNLIMITED_SELECT) || defined(_DARWIN_C_SOURCE)
---        return __darwin_check_fd_set_overflow(_a, _b, 1);
---#else
---        return __darwin_check_fd_set_overflow(_a, _b, 0);
---#endif
---    } else {
---        return 1;
---    }
---}
-
--- Across the internet there are many other reports of this issue
---  See: https://github.com/mono/mono/issues/19393
---     , https://github.com/sitsofe/fio/commit/b6a1e63a1ff607692a3caf3c2db2c3d575ba2320
-
--- The issue was originally reported in #19950
-
-
 -- Note [Undefined symbols in the RTS]
 -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 -- The RTS is built with a number of `-u` flags. This is to handle cyclic


=====================================
testsuite/tests/interface-stability/ghc-experimental-exports.stdout
=====================================
@@ -6155,6 +6155,157 @@ module GHC.Profiling.Eras where
   incrementUserEra :: GHC.Types.Word -> GHC.Types.IO GHC.Types.Word
   setUserEra :: GHC.Types.Word -> GHC.Types.IO ()
 
+module GHC.RTS.Flags.Experimental where
+  -- Safety: None
+  type CCFlags :: *
+  data CCFlags = CCFlags {doCostCentres :: DoCostCentres, profilerTicks :: GHC.Types.Int, msecsPerTick :: GHC.Types.Int}
+  type ConcFlags :: *
+  data ConcFlags = ConcFlags {ctxtSwitchTime :: RtsTime, ctxtSwitchTicks :: GHC.Types.Int}
+  type DebugFlags :: *
+  data DebugFlags = DebugFlags {scheduler :: GHC.Types.Bool, interpreter :: GHC.Types.Bool, weak :: GHC.Types.Bool, gccafs :: GHC.Types.Bool, gc :: GHC.Types.Bool, nonmoving_gc :: GHC.Types.Bool, block_alloc :: GHC.Types.Bool, sanity :: GHC.Types.Bool, stable :: GHC.Types.Bool, prof :: GHC.Types.Bool, linker :: GHC.Types.Bool, apply :: GHC.Types.Bool, stm :: GHC.Types.Bool, squeeze :: GHC.Types.Bool, hpc :: GHC.Types.Bool, sparks :: GHC.Types.Bool}
+  type DoCostCentres :: *
+  data DoCostCentres = CostCentresNone | CostCentresSummary | CostCentresVerbose | CostCentresAll | CostCentresJSON
+  type DoHeapProfile :: *
+  data DoHeapProfile = NoHeapProfiling | HeapByCCS | HeapByMod | HeapByDescr | HeapByType | HeapByRetainer | HeapByLDV | HeapByClosureType | HeapByInfoTable | HeapByEra
+  type DoTrace :: *
+  data DoTrace = TraceNone | TraceEventLog | TraceStderr
+  type GCFlags :: *
+  data GCFlags
+    = GCFlags {statsFile :: GHC.Internal.Maybe.Maybe GHC.Internal.IO.FilePath,
+               giveStats :: GiveGCStats,
+               maxStkSize :: GHC.Internal.Word.Word32,
+               initialStkSize :: GHC.Internal.Word.Word32,
+               stkChunkSize :: GHC.Internal.Word.Word32,
+               stkChunkBufferSize :: GHC.Internal.Word.Word32,
+               maxHeapSize :: GHC.Internal.Word.Word32,
+               minAllocAreaSize :: GHC.Internal.Word.Word32,
+               largeAllocLim :: GHC.Internal.Word.Word32,
+               nurseryChunkSize :: GHC.Internal.Word.Word32,
+               minOldGenSize :: GHC.Internal.Word.Word32,
+               heapSizeSuggestion :: GHC.Internal.Word.Word32,
+               heapSizeSuggestionAuto :: GHC.Types.Bool,
+               oldGenFactor :: GHC.Types.Double,
+               returnDecayFactor :: GHC.Types.Double,
+               pcFreeHeap :: GHC.Types.Double,
+               generations :: GHC.Internal.Word.Word32,
+               squeezeUpdFrames :: GHC.Types.Bool,
+               compact :: GHC.Types.Bool,
+               compactThreshold :: GHC.Types.Double,
+               sweep :: GHC.Types.Bool,
+               ringBell :: GHC.Types.Bool,
+               idleGCDelayTime :: RtsTime,
+               doIdleGC :: GHC.Types.Bool,
+               heapBase :: GHC.Types.Word,
+               allocLimitGrace :: GHC.Types.Word,
+               numa :: GHC.Types.Bool,
+               numaMask :: GHC.Types.Word}
+  type GiveGCStats :: *
+  data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats
+  type HpcFlags :: *
+  data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool}
+  type IoManagerFlag :: *
+  data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy
+  type IoSubSystem :: *
+  data IoSubSystem = IoPOSIX | IoNative
+  type MiscFlags :: *
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  type ParFlags :: *
+  data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
+  type ProfFlags :: *
+  data ProfFlags
+    = ProfFlags {doHeapProfile :: DoHeapProfile,
+                 heapProfileInterval :: RtsTime,
+                 heapProfileIntervalTicks :: GHC.Types.Word,
+                 startHeapProfileAtStartup :: GHC.Types.Bool,
+                 startTimeProfileAtStartup :: GHC.Types.Bool,
+                 showCCSOnException :: GHC.Types.Bool,
+                 automaticEraIncrement :: GHC.Types.Bool,
+                 maxRetainerSetSize :: GHC.Types.Word,
+                 ccsLength :: GHC.Types.Word,
+                 modSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 descrSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 typeSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 ccSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 ccsSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 retainerSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 bioSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 eraSelector :: GHC.Types.Word}
+  type RTSFlags :: *
+  data RTSFlags = RTSFlags {gcFlags :: GCFlags, concurrentFlags :: ConcFlags, miscFlags :: MiscFlags, debugFlags :: DebugFlags, costCentreFlags :: CCFlags, profilingFlags :: ProfFlags, traceFlags :: TraceFlags, tickyFlags :: TickyFlags, parFlags :: ParFlags, hpcFlags :: HpcFlags}
+  type RtsTime :: *
+  type RtsTime = GHC.Internal.Word.Word64
+  type TickyFlags :: *
+  data TickyFlags = TickyFlags {showTickyStats :: GHC.Types.Bool, tickyFile :: GHC.Internal.Maybe.Maybe GHC.Internal.IO.FilePath}
+  type TraceFlags :: *
+  data TraceFlags = TraceFlags {tracing :: DoTrace, timestamp :: GHC.Types.Bool, traceScheduler :: GHC.Types.Bool, traceGc :: GHC.Types.Bool, traceNonmovingGc :: GHC.Types.Bool, sparksSampled :: GHC.Types.Bool, sparksFull :: GHC.Types.Bool, user :: GHC.Types.Bool}
+  getCCFlags :: GHC.Types.IO CCFlags
+  getConcFlags :: GHC.Types.IO ConcFlags
+  getDebugFlags :: GHC.Types.IO DebugFlags
+  getGCFlags :: GHC.Types.IO GCFlags
+  getHpcFlags :: GHC.Types.IO HpcFlags
+  getMiscFlags :: GHC.Types.IO MiscFlags
+  getParFlags :: GHC.Types.IO ParFlags
+  getProfFlags :: GHC.Types.IO ProfFlags
+  getRTSFlags :: GHC.Types.IO RTSFlags
+  getTickyFlags :: GHC.Types.IO TickyFlags
+  getTraceFlags :: GHC.Types.IO TraceFlags
+
+module GHC.Stats.Experimental where
+  -- Safety: Safe
+  type GCDetails :: *
+  data GCDetails
+    = GCDetails {gcdetails_gen :: GHC.Internal.Word.Word32,
+                 gcdetails_threads :: GHC.Internal.Word.Word32,
+                 gcdetails_allocated_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_live_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_large_objects_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_compact_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_slop_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_mem_in_use_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_copied_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_par_max_copied_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_par_balanced_copied_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_block_fragmentation_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_sync_elapsed_ns :: RtsTime,
+                 gcdetails_cpu_ns :: RtsTime,
+                 gcdetails_elapsed_ns :: RtsTime,
+                 gcdetails_nonmoving_gc_sync_cpu_ns :: RtsTime,
+                 gcdetails_nonmoving_gc_sync_elapsed_ns :: RtsTime}
+  type RTSStats :: *
+  data RTSStats
+    = RTSStats {gcs :: GHC.Internal.Word.Word32,
+                major_gcs :: GHC.Internal.Word.Word32,
+                allocated_bytes :: GHC.Internal.Word.Word64,
+                max_live_bytes :: GHC.Internal.Word.Word64,
+                max_large_objects_bytes :: GHC.Internal.Word.Word64,
+                max_compact_bytes :: GHC.Internal.Word.Word64,
+                max_slop_bytes :: GHC.Internal.Word.Word64,
+                max_mem_in_use_bytes :: GHC.Internal.Word.Word64,
+                cumulative_live_bytes :: GHC.Internal.Word.Word64,
+                copied_bytes :: GHC.Internal.Word.Word64,
+                par_copied_bytes :: GHC.Internal.Word.Word64,
+                cumulative_par_max_copied_bytes :: GHC.Internal.Word.Word64,
+                cumulative_par_balanced_copied_bytes :: GHC.Internal.Word.Word64,
+                init_cpu_ns :: RtsTime,
+                init_elapsed_ns :: RtsTime,
+                mutator_cpu_ns :: RtsTime,
+                mutator_elapsed_ns :: RtsTime,
+                gc_cpu_ns :: RtsTime,
+                gc_elapsed_ns :: RtsTime,
+                cpu_ns :: RtsTime,
+                elapsed_ns :: RtsTime,
+                nonmoving_gc_sync_cpu_ns :: RtsTime,
+                nonmoving_gc_sync_elapsed_ns :: RtsTime,
+                nonmoving_gc_sync_max_elapsed_ns :: RtsTime,
+                nonmoving_gc_cpu_ns :: RtsTime,
+                nonmoving_gc_elapsed_ns :: RtsTime,
+                nonmoving_gc_max_elapsed_ns :: RtsTime,
+                gc :: GCDetails}
+  type RtsTime :: *
+  type RtsTime = GHC.Internal.Int.Int64
+  getRTSStats :: GHC.Types.IO RTSStats
+  getRTSStatsEnabled :: GHC.Types.IO GHC.Types.Bool
+
 module GHC.TypeLits.Experimental where
   -- Safety: Safe-Inferred
   appendSSymbol :: forall (a :: GHC.Types.Symbol) (b :: GHC.Types.Symbol). GHC.Internal.TypeLits.SSymbol a -> GHC.Internal.TypeLits.SSymbol b -> GHC.Internal.TypeLits.SSymbol (GHC.Internal.TypeLits.AppendSymbol a b)
@@ -10558,9 +10709,31 @@ instance forall a. GHC.Internal.Data.String.IsString a => GHC.Internal.Data.Stri
 instance forall a. (a ~ GHC.Types.Char) => GHC.Internal.Data.String.IsString [a] -- Defined in ‘GHC.Internal.Data.String’
 instance forall a. GHC.Internal.Enum.Bounded a => GHC.Internal.Enum.Bounded (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. (GHC.Internal.Enum.Enum a, GHC.Internal.Enum.Bounded a, GHC.Classes.Eq a) => GHC.Internal.Enum.Enum (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoCostCentres -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoHeapProfile -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
 instance forall a. GHC.Internal.Float.Floating a => GHC.Internal.Float.Floating (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Float.RealFloat (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 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’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.CCFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.ConcFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.DebugFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.DoCostCentres -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.DoHeapProfile -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.GCFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.HpcFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.MiscFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.ParFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.ProfFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.RTSFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.TickyFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.TraceFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.Stats.GCDetails -- Defined in ‘GHC.Internal.Stats’
+instance GHC.Internal.Generics.Generic GHC.Internal.Stats.RTSStats -- Defined in ‘GHC.Internal.Stats’
 instance GHC.Internal.IsList.IsList GHC.Internal.Stack.Types.CallStack -- Defined in ‘GHC.Internal.IsList’
 instance forall a. GHC.Internal.IsList.IsList [a] -- Defined in ‘GHC.Internal.IsList’
 instance forall a. GHC.Internal.IsList.IsList (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.IsList’
@@ -10569,6 +10742,8 @@ instance forall a. GHC.Internal.IsList.IsList (GHC.Internal.Functor.ZipList.ZipL
 instance forall a. GHC.Internal.Ix.Ix a => GHC.Internal.Ix.Ix (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Num.Num a => GHC.Internal.Num.Num (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Read.Read a => GHC.Internal.Read.Read (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
+instance GHC.Internal.Read.Read GHC.Internal.Stats.GCDetails -- Defined in ‘GHC.Internal.Stats’
+instance GHC.Internal.Read.Read GHC.Internal.Stats.RTSStats -- Defined in ‘GHC.Internal.Stats’
 instance forall a. GHC.Internal.Real.Fractional a => GHC.Internal.Real.Fractional (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Real.Real a => GHC.Internal.Real.Real (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Real.RealFrac a => GHC.Internal.Real.RealFrac (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
@@ -10576,6 +10751,24 @@ instance forall a. GHC.Internal.Show.Show a => GHC.Internal.Show.Show (GHC.Inter
 instance forall a. GHC.Internal.Show.Show (GHC.Internal.Ptr.FunPtr a) -- Defined in ‘GHC.Internal.Ptr’
 instance forall a. GHC.Internal.Show.Show (GHC.Internal.Ptr.Ptr a) -- Defined in ‘GHC.Internal.Ptr’
 instance GHC.Internal.Show.Show GHC.Internal.IO.MaskingState -- Defined in ‘GHC.Internal.IO’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.CCFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.ConcFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.DebugFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.DoCostCentres -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.DoHeapProfile -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.GCFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.HpcFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.MiscFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.ParFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.ProfFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.RTSFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.TickyFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.TraceFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.Stats.GCDetails -- Defined in ‘GHC.Internal.Stats’
+instance GHC.Internal.Show.Show GHC.Internal.Stats.RTSStats -- Defined in ‘GHC.Internal.Stats’
 instance GHC.Classes.Eq GHC.Types.Bool -- Defined in ‘GHC.Classes’
 instance GHC.Classes.Eq GHC.Types.Char -- Defined in ‘GHC.Classes’
 instance GHC.Classes.Eq GHC.Types.Double -- Defined in ‘GHC.Classes’
@@ -10610,6 +10803,8 @@ instance forall a. GHC.Classes.Eq (GHC.Internal.Ptr.Ptr a) -- Defined in ‘GHC.
 instance forall a. GHC.Classes.Eq a => GHC.Classes.Eq (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.Base’
 instance GHC.Classes.Eq GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Base’
 instance GHC.Classes.Eq GHC.Internal.IO.MaskingState -- Defined in ‘GHC.Internal.IO’
+instance GHC.Classes.Eq GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Classes.Eq GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
 instance GHC.Classes.Ord GHC.Types.Bool -- Defined in ‘GHC.Classes’
 instance GHC.Classes.Ord GHC.Types.Char -- Defined in ‘GHC.Classes’
 instance GHC.Classes.Ord GHC.Types.Double -- Defined in ‘GHC.Classes’


=====================================
testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
=====================================
@@ -6158,6 +6158,157 @@ module GHC.Profiling.Eras where
   incrementUserEra :: GHC.Types.Word -> GHC.Types.IO GHC.Types.Word
   setUserEra :: GHC.Types.Word -> GHC.Types.IO ()
 
+module GHC.RTS.Flags.Experimental where
+  -- Safety: None
+  type CCFlags :: *
+  data CCFlags = CCFlags {doCostCentres :: DoCostCentres, profilerTicks :: GHC.Types.Int, msecsPerTick :: GHC.Types.Int}
+  type ConcFlags :: *
+  data ConcFlags = ConcFlags {ctxtSwitchTime :: RtsTime, ctxtSwitchTicks :: GHC.Types.Int}
+  type DebugFlags :: *
+  data DebugFlags = DebugFlags {scheduler :: GHC.Types.Bool, interpreter :: GHC.Types.Bool, weak :: GHC.Types.Bool, gccafs :: GHC.Types.Bool, gc :: GHC.Types.Bool, nonmoving_gc :: GHC.Types.Bool, block_alloc :: GHC.Types.Bool, sanity :: GHC.Types.Bool, stable :: GHC.Types.Bool, prof :: GHC.Types.Bool, linker :: GHC.Types.Bool, apply :: GHC.Types.Bool, stm :: GHC.Types.Bool, squeeze :: GHC.Types.Bool, hpc :: GHC.Types.Bool, sparks :: GHC.Types.Bool}
+  type DoCostCentres :: *
+  data DoCostCentres = CostCentresNone | CostCentresSummary | CostCentresVerbose | CostCentresAll | CostCentresJSON
+  type DoHeapProfile :: *
+  data DoHeapProfile = NoHeapProfiling | HeapByCCS | HeapByMod | HeapByDescr | HeapByType | HeapByRetainer | HeapByLDV | HeapByClosureType | HeapByInfoTable | HeapByEra
+  type DoTrace :: *
+  data DoTrace = TraceNone | TraceEventLog | TraceStderr
+  type GCFlags :: *
+  data GCFlags
+    = GCFlags {statsFile :: GHC.Internal.Maybe.Maybe GHC.Internal.IO.FilePath,
+               giveStats :: GiveGCStats,
+               maxStkSize :: GHC.Internal.Word.Word32,
+               initialStkSize :: GHC.Internal.Word.Word32,
+               stkChunkSize :: GHC.Internal.Word.Word32,
+               stkChunkBufferSize :: GHC.Internal.Word.Word32,
+               maxHeapSize :: GHC.Internal.Word.Word32,
+               minAllocAreaSize :: GHC.Internal.Word.Word32,
+               largeAllocLim :: GHC.Internal.Word.Word32,
+               nurseryChunkSize :: GHC.Internal.Word.Word32,
+               minOldGenSize :: GHC.Internal.Word.Word32,
+               heapSizeSuggestion :: GHC.Internal.Word.Word32,
+               heapSizeSuggestionAuto :: GHC.Types.Bool,
+               oldGenFactor :: GHC.Types.Double,
+               returnDecayFactor :: GHC.Types.Double,
+               pcFreeHeap :: GHC.Types.Double,
+               generations :: GHC.Internal.Word.Word32,
+               squeezeUpdFrames :: GHC.Types.Bool,
+               compact :: GHC.Types.Bool,
+               compactThreshold :: GHC.Types.Double,
+               sweep :: GHC.Types.Bool,
+               ringBell :: GHC.Types.Bool,
+               idleGCDelayTime :: RtsTime,
+               doIdleGC :: GHC.Types.Bool,
+               heapBase :: GHC.Types.Word,
+               allocLimitGrace :: GHC.Types.Word,
+               numa :: GHC.Types.Bool,
+               numaMask :: GHC.Types.Word}
+  type GiveGCStats :: *
+  data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats
+  type HpcFlags :: *
+  data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool}
+  type IoManagerFlag :: *
+  data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy
+  type IoSubSystem :: *
+  data IoSubSystem = IoPOSIX | IoNative
+  type MiscFlags :: *
+  data MiscFlags = MiscFlags {tickInterval :: RtsTime, installSignalHandlers :: GHC.Types.Bool, installSEHHandlers :: GHC.Types.Bool, generateCrashDumpFile :: GHC.Types.Bool, generateStackTrace :: GHC.Types.Bool, machineReadable :: GHC.Types.Bool, disableDelayedOsMemoryReturn :: GHC.Types.Bool, internalCounters :: GHC.Types.Bool, linkerAlwaysPic :: GHC.Types.Bool, linkerMemBase :: GHC.Types.Word, ioManager :: IoManagerFlag, numIoWorkerThreads :: GHC.Internal.Word.Word32}
+  type ParFlags :: *
+  data ParFlags = ParFlags {nCapabilities :: GHC.Internal.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Internal.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Internal.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Internal.Word.Word32, parGcNoSyncWithIdle :: GHC.Internal.Word.Word32, parGcThreads :: GHC.Internal.Word.Word32, setAffinity :: GHC.Types.Bool}
+  type ProfFlags :: *
+  data ProfFlags
+    = ProfFlags {doHeapProfile :: DoHeapProfile,
+                 heapProfileInterval :: RtsTime,
+                 heapProfileIntervalTicks :: GHC.Types.Word,
+                 startHeapProfileAtStartup :: GHC.Types.Bool,
+                 startTimeProfileAtStartup :: GHC.Types.Bool,
+                 showCCSOnException :: GHC.Types.Bool,
+                 automaticEraIncrement :: GHC.Types.Bool,
+                 maxRetainerSetSize :: GHC.Types.Word,
+                 ccsLength :: GHC.Types.Word,
+                 modSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 descrSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 typeSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 ccSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 ccsSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 retainerSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 bioSelector :: GHC.Internal.Maybe.Maybe GHC.Internal.Base.String,
+                 eraSelector :: GHC.Types.Word}
+  type RTSFlags :: *
+  data RTSFlags = RTSFlags {gcFlags :: GCFlags, concurrentFlags :: ConcFlags, miscFlags :: MiscFlags, debugFlags :: DebugFlags, costCentreFlags :: CCFlags, profilingFlags :: ProfFlags, traceFlags :: TraceFlags, tickyFlags :: TickyFlags, parFlags :: ParFlags, hpcFlags :: HpcFlags}
+  type RtsTime :: *
+  type RtsTime = GHC.Internal.Word.Word64
+  type TickyFlags :: *
+  data TickyFlags = TickyFlags {showTickyStats :: GHC.Types.Bool, tickyFile :: GHC.Internal.Maybe.Maybe GHC.Internal.IO.FilePath}
+  type TraceFlags :: *
+  data TraceFlags = TraceFlags {tracing :: DoTrace, timestamp :: GHC.Types.Bool, traceScheduler :: GHC.Types.Bool, traceGc :: GHC.Types.Bool, traceNonmovingGc :: GHC.Types.Bool, sparksSampled :: GHC.Types.Bool, sparksFull :: GHC.Types.Bool, user :: GHC.Types.Bool}
+  getCCFlags :: GHC.Types.IO CCFlags
+  getConcFlags :: GHC.Types.IO ConcFlags
+  getDebugFlags :: GHC.Types.IO DebugFlags
+  getGCFlags :: GHC.Types.IO GCFlags
+  getHpcFlags :: GHC.Types.IO HpcFlags
+  getMiscFlags :: GHC.Types.IO MiscFlags
+  getParFlags :: GHC.Types.IO ParFlags
+  getProfFlags :: GHC.Types.IO ProfFlags
+  getRTSFlags :: GHC.Types.IO RTSFlags
+  getTickyFlags :: GHC.Types.IO TickyFlags
+  getTraceFlags :: GHC.Types.IO TraceFlags
+
+module GHC.Stats.Experimental where
+  -- Safety: Safe
+  type GCDetails :: *
+  data GCDetails
+    = GCDetails {gcdetails_gen :: GHC.Internal.Word.Word32,
+                 gcdetails_threads :: GHC.Internal.Word.Word32,
+                 gcdetails_allocated_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_live_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_large_objects_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_compact_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_slop_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_mem_in_use_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_copied_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_par_max_copied_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_par_balanced_copied_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_block_fragmentation_bytes :: GHC.Internal.Word.Word64,
+                 gcdetails_sync_elapsed_ns :: RtsTime,
+                 gcdetails_cpu_ns :: RtsTime,
+                 gcdetails_elapsed_ns :: RtsTime,
+                 gcdetails_nonmoving_gc_sync_cpu_ns :: RtsTime,
+                 gcdetails_nonmoving_gc_sync_elapsed_ns :: RtsTime}
+  type RTSStats :: *
+  data RTSStats
+    = RTSStats {gcs :: GHC.Internal.Word.Word32,
+                major_gcs :: GHC.Internal.Word.Word32,
+                allocated_bytes :: GHC.Internal.Word.Word64,
+                max_live_bytes :: GHC.Internal.Word.Word64,
+                max_large_objects_bytes :: GHC.Internal.Word.Word64,
+                max_compact_bytes :: GHC.Internal.Word.Word64,
+                max_slop_bytes :: GHC.Internal.Word.Word64,
+                max_mem_in_use_bytes :: GHC.Internal.Word.Word64,
+                cumulative_live_bytes :: GHC.Internal.Word.Word64,
+                copied_bytes :: GHC.Internal.Word.Word64,
+                par_copied_bytes :: GHC.Internal.Word.Word64,
+                cumulative_par_max_copied_bytes :: GHC.Internal.Word.Word64,
+                cumulative_par_balanced_copied_bytes :: GHC.Internal.Word.Word64,
+                init_cpu_ns :: RtsTime,
+                init_elapsed_ns :: RtsTime,
+                mutator_cpu_ns :: RtsTime,
+                mutator_elapsed_ns :: RtsTime,
+                gc_cpu_ns :: RtsTime,
+                gc_elapsed_ns :: RtsTime,
+                cpu_ns :: RtsTime,
+                elapsed_ns :: RtsTime,
+                nonmoving_gc_sync_cpu_ns :: RtsTime,
+                nonmoving_gc_sync_elapsed_ns :: RtsTime,
+                nonmoving_gc_sync_max_elapsed_ns :: RtsTime,
+                nonmoving_gc_cpu_ns :: RtsTime,
+                nonmoving_gc_elapsed_ns :: RtsTime,
+                nonmoving_gc_max_elapsed_ns :: RtsTime,
+                gc :: GCDetails}
+  type RtsTime :: *
+  type RtsTime = GHC.Internal.Int.Int64
+  getRTSStats :: GHC.Types.IO RTSStats
+  getRTSStatsEnabled :: GHC.Types.IO GHC.Types.Bool
+
 module GHC.TypeLits.Experimental where
   -- Safety: Safe-Inferred
   appendSSymbol :: forall (a :: GHC.Types.Symbol) (b :: GHC.Types.Symbol). GHC.Internal.TypeLits.SSymbol a -> GHC.Internal.TypeLits.SSymbol b -> GHC.Internal.TypeLits.SSymbol (GHC.Internal.TypeLits.AppendSymbol a b)
@@ -10561,9 +10712,31 @@ instance forall a. GHC.Internal.Data.String.IsString a => GHC.Internal.Data.Stri
 instance forall a. (a ~ GHC.Types.Char) => GHC.Internal.Data.String.IsString [a] -- Defined in ‘GHC.Internal.Data.String’
 instance forall a. GHC.Internal.Enum.Bounded a => GHC.Internal.Enum.Bounded (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. (GHC.Internal.Enum.Enum a, GHC.Internal.Enum.Bounded a, GHC.Classes.Eq a) => GHC.Internal.Enum.Enum (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoCostCentres -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoHeapProfile -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Enum.Enum GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
 instance forall a. GHC.Internal.Float.Floating a => GHC.Internal.Float.Floating (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Float.RealFloat a => GHC.Internal.Float.RealFloat (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 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’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.CCFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.ConcFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.DebugFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.DoCostCentres -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.DoHeapProfile -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.GCFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.HpcFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.MiscFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.ParFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.ProfFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.RTSFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.TickyFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.RTS.Flags.TraceFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Generics.Generic GHC.Internal.Stats.GCDetails -- Defined in ‘GHC.Internal.Stats’
+instance GHC.Internal.Generics.Generic GHC.Internal.Stats.RTSStats -- Defined in ‘GHC.Internal.Stats’
 instance GHC.Internal.IsList.IsList GHC.Internal.Stack.Types.CallStack -- Defined in ‘GHC.Internal.IsList’
 instance forall a. GHC.Internal.IsList.IsList [a] -- Defined in ‘GHC.Internal.IsList’
 instance forall a. GHC.Internal.IsList.IsList (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.IsList’
@@ -10572,6 +10745,8 @@ instance forall a. GHC.Internal.IsList.IsList (GHC.Internal.Functor.ZipList.ZipL
 instance forall a. GHC.Internal.Ix.Ix a => GHC.Internal.Ix.Ix (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Num.Num a => GHC.Internal.Num.Num (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Read.Read a => GHC.Internal.Read.Read (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
+instance GHC.Internal.Read.Read GHC.Internal.Stats.GCDetails -- Defined in ‘GHC.Internal.Stats’
+instance GHC.Internal.Read.Read GHC.Internal.Stats.RTSStats -- Defined in ‘GHC.Internal.Stats’
 instance forall a. GHC.Internal.Real.Fractional a => GHC.Internal.Real.Fractional (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Real.Real a => GHC.Internal.Real.Real (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
 instance forall a. GHC.Internal.Real.RealFrac a => GHC.Internal.Real.RealFrac (GHC.Internal.Data.Ord.Down a) -- Defined in ‘GHC.Internal.Data.Ord’
@@ -10579,6 +10754,24 @@ instance forall a. GHC.Internal.Show.Show a => GHC.Internal.Show.Show (GHC.Inter
 instance forall a. GHC.Internal.Show.Show (GHC.Internal.Ptr.FunPtr a) -- Defined in ‘GHC.Internal.Ptr’
 instance forall a. GHC.Internal.Show.Show (GHC.Internal.Ptr.Ptr a) -- Defined in ‘GHC.Internal.Ptr’
 instance GHC.Internal.Show.Show GHC.Internal.IO.MaskingState -- Defined in ‘GHC.Internal.IO’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.CCFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.ConcFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.DebugFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.DoCostCentres -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.DoHeapProfile -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.DoTrace -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.GCFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.GiveGCStats -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.HpcFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.MiscFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.ParFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.ProfFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.RTSFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.TickyFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.RTS.Flags.TraceFlags -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Internal.Show.Show GHC.Internal.Stats.GCDetails -- Defined in ‘GHC.Internal.Stats’
+instance GHC.Internal.Show.Show GHC.Internal.Stats.RTSStats -- Defined in ‘GHC.Internal.Stats’
 instance GHC.Classes.Eq GHC.Types.Bool -- Defined in ‘GHC.Classes’
 instance GHC.Classes.Eq GHC.Types.Char -- Defined in ‘GHC.Classes’
 instance GHC.Classes.Eq GHC.Types.Double -- Defined in ‘GHC.Classes’
@@ -10613,6 +10806,8 @@ instance forall a. GHC.Classes.Eq (GHC.Internal.Ptr.Ptr a) -- Defined in ‘GHC.
 instance forall a. GHC.Classes.Eq a => GHC.Classes.Eq (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.Base’
 instance GHC.Classes.Eq GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.Base’
 instance GHC.Classes.Eq GHC.Internal.IO.MaskingState -- Defined in ‘GHC.Internal.IO’
+instance GHC.Classes.Eq GHC.Internal.RTS.Flags.IoManagerFlag -- Defined in ‘GHC.Internal.RTS.Flags’
+instance GHC.Classes.Eq GHC.Internal.IO.SubSystem.IoSubSystem -- Defined in ‘GHC.Internal.IO.SubSystem’
 instance GHC.Classes.Ord GHC.Types.Bool -- Defined in ‘GHC.Classes’
 instance GHC.Classes.Ord GHC.Types.Char -- Defined in ‘GHC.Classes’
 instance GHC.Classes.Ord GHC.Types.Double -- Defined in ‘GHC.Classes’



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b5bd6dd6c4b02507de6a71cbd153855b714b5525...8522f16f0e1de5601d1ca60b16b1e82f941f04bd

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b5bd6dd6c4b02507de6a71cbd153855b714b5525...8522f16f0e1de5601d1ca60b16b1e82f941f04bd
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/20241126/0f882bc3/attachment-0001.html>


More information about the ghc-commits mailing list