[Git][ghc/ghc][wip/con-info] 4 commits: Add a flag to control distinct constructor tables

Matthew Pickering gitlab at gitlab.haskell.org
Tue Nov 3 11:25:39 UTC 2020



Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC


Commits:
ec3c5fa0 by Matthew Pickering at 2020-11-03T11:24:18+00:00
Add a flag to control distinct constructor tables

- - - - -
4c01d7e5 by Matthew Pickering at 2020-11-03T11:25:05+00:00
small fixes to diff

- - - - -
9f4e3ea3 by Matthew Pickering at 2020-11-03T11:25:14+00:00
Start of note

- - - - -
343040a9 by Matthew Pickering at 2020-11-03T11:25:22+00:00
More clear name in eventlog

- - - - -


7 changed files:

- compiler/GHC/CoreToStg.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/StgToCmm/Types.hs
- rts/eventlog/EventLog.c


Changes:

=====================================
compiler/GHC/CoreToStg.hs
=====================================
@@ -925,7 +925,7 @@ lookupBinding env v = case lookupVarEnv env v of
 
 incDc :: DataCon -> CtsM (Maybe Int)
 incDc dc | isUnboxedTupleDataCon dc = return Nothing
-incDc dc = CtsM $ \_ _ -> do
+incDc dc = CtsM $ \dflags _ -> if not (gopt Opt_DistinctConstructorTables dflags) then return Nothing else do
           env <- get
           cc <- ask
           let dcMap' = alterUniqMap (maybe (Just [(0, cc)]) (\xs@((k, _):_) -> Just ((k + 1, cc) : xs))) (provDC env) dc


=====================================
compiler/GHC/Driver/CodeOutput.hs
=====================================
@@ -111,10 +111,10 @@ codeOutput dflags this_mod filenm location foreign_fps pkg_deps genForeignStubs
         ; a <- case backend dflags of
                  NCG         -> outputAsm dflags this_mod location filenm
                                              linted_cmm_stream
-                 ViaC           -> outputC dflags filenm linted_cmm_stream pkg_deps
+                 ViaC        -> outputC dflags filenm linted_cmm_stream pkg_deps
                  LLVM        -> outputLlvm dflags filenm linted_cmm_stream
-                 Interpreter -> panic "codeOutput: HscInterpreted"
-                 NoBackend     -> panic "codeOutput: HscNothing"
+                 Interpreter -> panic "codeOutput: Interpreter"
+                 NoBackend   -> panic "codeOutput: NoBackend"
         ; stubs <- genForeignStubs
         ; stubs_exist <- outputForeignStubs dflags this_mod location stubs
         ; return (filenm, stubs_exist, foreign_fps, a)
@@ -311,6 +311,7 @@ profilingInitCode platform this_mod (local_CCs, singleton_CCSs)
 
 
 -- | Generate code to initialise info pointer origin
+-- See note [Mapping Info Tables to Source Positions]
 ipInitCode :: [CmmInfoTable] -> DynFlags -> Module -> InfoTableProvMap -> SDoc
 ipInitCode used_info dflags this_mod (InfoTableProvMap dcmap closure_map)
  = if not (sccProfilingEnabled dflags)
@@ -342,4 +343,50 @@ ipInitCode used_info dflags this_mod (InfoTableProvMap dcmap closure_map)
       <> semi
 
 
+{-
+Note [Mapping Info Tables to Source Positions]
+
+When debugging memory issues it is very useful to be able to map a specific closure
+to a position in the source. The prime example is being able to map a THUNK to
+a specific place in the source program, the mapping is usually quite precise because
+a fresh info table is created for each distinct THUNK.
+
+There are two parts to the implementation
+
+1. The SourceNote information is used in order to give a source location to
+some specific closures.
+2. During code generation, a mapping from the info table to the statically
+determined location is emitted which can then be queried at runtime by
+various tools.
+
+-- Giving Source Locations to Closures
+
+### Thunks
+### Constructors
+
+
+
+
+-- Code Generation
+
+After the mapping has been collected during compilation, a C stub is generated which
+creates the static map from info table pointer to the information about where that
+info table was created from.
+
+This information can be consumed in two ways.
+
+1. The complete mapping is emitted into the eventlog so that external tools such
+as eventlog2html can use the information with the heap profile by info table mode.
+2. The `lookupIPE` function can be used via the `whereFrom#` primop to introspect
+information about a closure in a running Haskell program.
+
+Note [Distinct Info Tables for Constructors]
+
+In the old times, each usage of a data constructor used the same info table.
+This made it impossible to distinguish which actual usuage of a data constructor was
+contributing primarily to the allocation in a program. Using the TODO flag you
+can cause code generation to generate a distinct info table for each usage of
+a constructor. Then, when inspecting the heap you can see precisely which usage of a constructor
+was responsible for each allocation.
 
+-}
\ No newline at end of file


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -130,6 +130,8 @@ data GeneralFlag
    | Opt_FastLlvm                       -- hidden flag
    | Opt_NoTypeableBinds
 
+   | Opt_DistinctConstructorTables
+
    | Opt_WarnIsError                    -- -Werror; makes warnings fatal
    | Opt_ShowWarnGroups                 -- Show the group a warning belongs to
    | Opt_HideSourcePaths                -- Hide module source/object paths


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -218,7 +218,6 @@ import GHC.Unit.Module.Status
 import GHC.Unit.Module.Imported
 import GHC.Unit.Module.Graph
 import GHC.Unit.Home.ModInfo
-import GHC.Types.Name.Set
 import GHC.Unit.Home
 import GHC.Unit.State
 import GHC.Unit.Module.Deps
@@ -1643,7 +1642,7 @@ doCodeGen hsc_env this_mod denv data_tycons
             Stream.mapAccumL_ (cmmPipeline hsc_env) (emptySRT this_mod) ppr_stream1
               <&> first (srtMapNonCAFs . moduleSRTMap)
 
-          return CgInfos{ cgNonCafs = non_cafs, cgLFInfos = lf_infos, cgNameSet = emptyNameSet }
+          return CgInfos{ cgNonCafs = non_cafs, cgLFInfos = lf_infos }
 
         dump2 a = do
           unless (null a) $


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2914,6 +2914,8 @@ dynamic_flags_deps = [
   , make_ord_flag defGhcFlag "fno-prof-auto"
       (noArg (\d -> d { profAuto = NoProfAuto } ))
 
+  , make_ord_flag defGhcFlag "fdistinct-constructor-tables"
+      (NoArg (setGeneralFlag Opt_DistinctConstructorTables))
         ------ Compiler flags -----------------------------------------------
 
   , make_ord_flag defGhcFlag "fasm"             (NoArg (setObjBackend NCG))


=====================================
compiler/GHC/StgToCmm/Types.hs
=====================================
@@ -86,7 +86,6 @@ data CgInfos = CgInfos
       -- either not exported of CAFFY.
   , cgLFInfos :: !ModuleLFInfos
       -- ^ LambdaFormInfos of exported closures in the current module.
-  , cgNameSet :: !NameSet
   }
 
 --------------------------------------------------------------------------------


=====================================
rts/eventlog/EventLog.c
=====================================
@@ -104,7 +104,7 @@ char *EventDesc[] = {
   [EVENT_HACK_BUG_T9003]      = "Empty event for bug #9003",
   [EVENT_HEAP_PROF_BEGIN]     = "Start of heap profile",
   [EVENT_HEAP_PROF_COST_CENTRE]   = "Cost center definition",
-  [EVENT_IPE]                      = "ITE",
+  [EVENT_IPE]                     = "Info Table Source Position",
   [EVENT_HEAP_PROF_SAMPLE_BEGIN]  = "Start of heap profile sample",
   [EVENT_HEAP_BIO_PROF_SAMPLE_BEGIN]  = "Start of heap profile (biographical) sample",
   [EVENT_HEAP_PROF_SAMPLE_END]    = "End of heap profile sample",



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d98f44c87c7b566e6ba2d499b30f8fbc8bbc9feb...343040a911599fc6096ac8bcc98f591360da1a9a

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d98f44c87c7b566e6ba2d499b30f8fbc8bbc9feb...343040a911599fc6096ac8bcc98f591360da1a9a
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/20201103/2d489ec6/attachment-0001.html>


More information about the ghc-commits mailing list