[Git][ghc/ghc][wip/eras-profiling-with-base] base: Reflect new era profiling RTS flags in GHC.RTS.Flags

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Mon Feb 12 11:50:58 UTC 2024



Matthew Pickering pushed to branch wip/eras-profiling-with-base at Glasgow Haskell Compiler / GHC


Commits:
265f375d by Matthew Pickering at 2024-02-12T11:50:49+00:00
base: Reflect new era profiling RTS flags in GHC.RTS.Flags

* -he profiling mode
* -he profiling selector
* --automatic-era-increment

- - - - -


3 changed files:

- libraries/base/changelog.md
- libraries/ghc-internal/src/GHC/RTS/Flags.hsc
- testsuite/tests/interface-stability/base-exports.stdout


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -38,6 +38,10 @@
 
   * Treat all FDs as "nonblocking" on wasm32 ([CLC proposal #234](https://github.com/haskell/core-libraries-committee/issues/234))
 
+  * Add `HeapByEra`, `eraSelector` and `automaticEraIncrement` to `GHC.RTS.Flags` to
+    reflect the new RTS flags: `-he` profiling mode, `-he` selector and `--automatic-era-increment`.
+    ([CLC proposal #254](https://github.com/haskell/core-libraries-committee/issues/254))
+
 ## 4.19.0.0 *October 2023*
   * Add `{-# WARNING in "x-partial" #-}` to `Data.List.{head,tail}`.
     Use `{-# OPTIONS_GHC -Wno-x-partial #-}` to disable it.


=====================================
libraries/ghc-internal/src/GHC/RTS/Flags.hsc
=====================================
@@ -272,6 +272,7 @@ data DoHeapProfile
     | HeapByLDV
     | HeapByClosureType
     | HeapByInfoTable
+    | HeapByEra
     deriving ( Show -- ^ @since 4.8.0.0
              , Generic -- ^ @since 4.15.0.0
              )
@@ -287,6 +288,7 @@ instance Enum DoHeapProfile where
     fromEnum HeapByLDV         = #{const HEAP_BY_LDV}
     fromEnum HeapByClosureType = #{const HEAP_BY_CLOSURE_TYPE}
     fromEnum HeapByInfoTable   = #{const HEAP_BY_INFO_TABLE}
+    fromEnum HeapByEra         = #{const HEAP_BY_ERA}
 
     toEnum #{const NO_HEAP_PROFILING}    = NoHeapProfiling
     toEnum #{const HEAP_BY_CCS}          = HeapByCCS
@@ -297,6 +299,7 @@ instance Enum DoHeapProfile where
     toEnum #{const HEAP_BY_LDV}          = HeapByLDV
     toEnum #{const HEAP_BY_CLOSURE_TYPE} = HeapByClosureType
     toEnum #{const HEAP_BY_INFO_TABLE}   = HeapByInfoTable
+    toEnum #{const HEAP_BY_ERA}          = HeapByEra
     toEnum e = errorWithoutStackTrace ("invalid enum for DoHeapProfile: " ++ show e)
 
 -- | Parameters of the cost-center profiler
@@ -308,6 +311,7 @@ data ProfFlags = ProfFlags
     , heapProfileIntervalTicks :: Word    -- ^ ticks between samples (derived)
     , startHeapProfileAtStartup :: Bool
     , showCCSOnException       :: Bool
+    , automaticEraIncrement    :: Bool
     , maxRetainerSetSize       :: Word
     , ccsLength                :: Word
     , modSelector              :: Maybe String
@@ -317,6 +321,7 @@ data ProfFlags = ProfFlags
     , ccsSelector              :: Maybe String
     , retainerSelector         :: Maybe String
     , bioSelector              :: Maybe String
+    , eraSelector              :: Word
     } deriving ( Show -- ^ @since 4.8.0.0
                , Generic -- ^ @since 4.15.0.0
                )
@@ -628,6 +633,8 @@ getProfFlags = do
                   (#{peek PROFILING_FLAGS, startHeapProfileAtStartup} ptr :: IO CBool))
             <*> (toBool <$>
                   (#{peek PROFILING_FLAGS, showCCSOnException} ptr :: IO CBool))
+            <*> (toBool <$>
+                  (#{peek PROFILING_FLAGS, incrementUserEra} ptr :: IO CBool))
             <*> #{peek PROFILING_FLAGS, maxRetainerSetSize} ptr
             <*> #{peek PROFILING_FLAGS, ccsLength} ptr
             <*> (peekCStringOpt =<< #{peek PROFILING_FLAGS, modSelector} ptr)
@@ -637,6 +644,7 @@ getProfFlags = do
             <*> (peekCStringOpt =<< #{peek PROFILING_FLAGS, ccsSelector} ptr)
             <*> (peekCStringOpt =<< #{peek PROFILING_FLAGS, retainerSelector} ptr)
             <*> (peekCStringOpt =<< #{peek PROFILING_FLAGS, bioSelector} ptr)
+            <*> #{peek PROFILING_FLAGS, eraSelector} ptr
 
 getTraceFlags :: IO TraceFlags
 getTraceFlags = do


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -9016,7 +9016,7 @@ module GHC.RTS.Flags where
   type DoCostCentres :: *
   data DoCostCentres = CostCentresNone | CostCentresSummary | CostCentresVerbose | CostCentresAll | CostCentresJSON
   type DoHeapProfile :: *
-  data DoHeapProfile = NoHeapProfiling | HeapByCCS | HeapByMod | HeapByDescr | HeapByType | HeapByRetainer | HeapByLDV | HeapByClosureType | HeapByInfoTable
+  data DoHeapProfile = NoHeapProfiling | HeapByCCS | HeapByMod | HeapByDescr | HeapByType | HeapByRetainer | HeapByLDV | HeapByClosureType | HeapByInfoTable | HeapByEra
   type DoTrace :: *
   data DoTrace = TraceNone | TraceEventLog | TraceStderr
   type GCFlags :: *
@@ -9060,7 +9060,23 @@ module GHC.RTS.Flags where
   type ParFlags :: *
   data ParFlags = ParFlags {nCapabilities :: GHC.Word.Word32, migrate :: GHC.Types.Bool, maxLocalSparks :: GHC.Word.Word32, parGcEnabled :: GHC.Types.Bool, parGcGen :: GHC.Word.Word32, parGcLoadBalancingEnabled :: GHC.Types.Bool, parGcLoadBalancingGen :: GHC.Word.Word32, parGcNoSyncWithIdle :: GHC.Word.Word32, parGcThreads :: GHC.Word.Word32, setAffinity :: GHC.Types.Bool}
   type ProfFlags :: *
-  data ProfFlags = ProfFlags {doHeapProfile :: DoHeapProfile, heapProfileInterval :: RtsTime, heapProfileIntervalTicks :: GHC.Types.Word, startHeapProfileAtStartup :: GHC.Types.Bool, showCCSOnException :: GHC.Types.Bool, maxRetainerSetSize :: GHC.Types.Word, ccsLength :: GHC.Types.Word, modSelector :: GHC.Maybe.Maybe GHC.Base.String, descrSelector :: GHC.Maybe.Maybe GHC.Base.String, typeSelector :: GHC.Maybe.Maybe GHC.Base.String, ccSelector :: GHC.Maybe.Maybe GHC.Base.String, ccsSelector :: GHC.Maybe.Maybe GHC.Base.String, retainerSelector :: GHC.Maybe.Maybe GHC.Base.String, bioSelector :: GHC.Maybe.Maybe GHC.Base.String}
+  data ProfFlags
+    = ProfFlags {doHeapProfile :: DoHeapProfile,
+                 heapProfileInterval :: RtsTime,
+                 heapProfileIntervalTicks :: GHC.Types.Word,
+                 startHeapProfileAtStartup :: GHC.Types.Bool,
+                 showCCSOnException :: GHC.Types.Bool,
+                 automaticEraIncrement :: GHC.Types.Bool,
+                 maxRetainerSetSize :: GHC.Types.Word,
+                 ccsLength :: GHC.Types.Word,
+                 modSelector :: GHC.Maybe.Maybe GHC.Base.String,
+                 descrSelector :: GHC.Maybe.Maybe GHC.Base.String,
+                 typeSelector :: GHC.Maybe.Maybe GHC.Base.String,
+                 ccSelector :: GHC.Maybe.Maybe GHC.Base.String,
+                 ccsSelector :: GHC.Maybe.Maybe GHC.Base.String,
+                 retainerSelector :: GHC.Maybe.Maybe GHC.Base.String,
+                 bioSelector :: GHC.Maybe.Maybe GHC.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 :: *



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/265f375d891d7e3cf892beecf24b178426beab1f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/265f375d891d7e3cf892beecf24b178426beab1f
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/20240212/44330794/attachment-0001.html>


More information about the ghc-commits mailing list