summaryrefslogtreecommitdiff
path: root/compiler/GHC/Stg/Debug.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Stg/Debug.hs')
-rw-r--r--compiler/GHC/Stg/Debug.hs122
1 files changed, 114 insertions, 8 deletions
diff --git a/compiler/GHC/Stg/Debug.hs b/compiler/GHC/Stg/Debug.hs
index e6e85f7db7..823334e2aa 100644
--- a/compiler/GHC/Stg/Debug.hs
+++ b/compiler/GHC/Stg/Debug.hs
@@ -16,7 +16,6 @@ import GHC.Unit.Module
import GHC.Types.Name ( getName, getOccName, occNameString, nameSrcSpan)
import GHC.Data.FastString
import GHC.Driver.Session
-import GHC.Driver.Ppr
import Control.Monad (when)
import Control.Monad.Trans.Reader
@@ -25,6 +24,8 @@ import Control.Monad.Trans.Class
import GHC.Types.Unique.Map
import GHC.Types.SrcLoc
import Control.Applicative
+import qualified Data.List.NonEmpty as NE
+import Data.List.NonEmpty (NonEmpty(..))
data SpanWithLabel = SpanWithLabel RealSrcSpan String
@@ -64,9 +65,9 @@ collectStgRhs bndr (StgRhsClosure ext cc us bs e)= do
e' <- collectExpr e
recordInfo bndr e'
return $ StgRhsClosure ext cc us bs e'
-collectStgRhs _bndr (StgRhsCon cc dc args) = do
- --n' <- incDc dc ticks
- return (StgRhsCon cc dc args)
+collectStgRhs _bndr (StgRhsCon cc dc _mn ticks args) = do
+ n' <- numberDataCon dc ticks
+ return (StgRhsCon cc dc n' ticks args)
recordInfo :: Id -> StgExpr -> M ()
@@ -86,9 +87,9 @@ collectExpr = go
where
go (StgApp occ as) = return $ StgApp occ as
go (StgLit lit) = return $ StgLit lit
- go (StgConApp dc as tys) = do
--- n' <- incDc dc []
- return (StgConApp dc as tys)
+ go (StgConApp dc _mn as tys) = do
+ n' <- numberDataCon dc []
+ return (StgConApp dc n' as tys)
go (StgOpApp op as ty) = return (StgOpApp op as ty)
go (StgCase scrut bndr ty alts) =
StgCase <$> collectExpr scrut <*> pure bndr <*> pure ty <*> mapM collectAlt alts
@@ -129,7 +130,6 @@ recordStgIdPosition :: Id -> Maybe SpanWithLabel -> Maybe SpanWithLabel -> M ()
recordStgIdPosition id best_span ss = do
dflags <- asks rDynFlags
when (gopt Opt_InfoTableMap dflags) $ do
- let tyString = showPpr dflags (idType id)
cc <- asks rSpan
--Useful for debugging why a certain Id gets given a certain span
--pprTraceM "recordStgIdPosition" (ppr id $$ ppr cc $$ ppr best_span $$ ppr ss)
@@ -138,3 +138,109 @@ recordStgIdPosition id best_span ss = do
Just (SpanWithLabel rss d) ->
lift $ modify (\env -> env { provClosure = addToUniqMap (provClosure env) (idName id) (idType id, rss, d)})
+numberDataCon :: DataCon -> [Tickish Id] -> M ConstructorNumber
+-- Unboxed tuples and sums do not allocate so they
+-- have no info tables.
+numberDataCon dc _ | isUnboxedTupleDataCon dc = return NoNumber
+numberDataCon dc _ | isUnboxedSumDataCon dc = return NoNumber
+numberDataCon dc ts = do
+ dflags <- asks rDynFlags
+ if not (gopt Opt_DistinctConstructorTables dflags) then return NoNumber else do
+ env <- lift get
+ mcc <- asks rSpan
+ let mbest_span = selectTick ts <|> mcc
+ case mbest_span of
+ Nothing -> return NoNumber
+ Just (SpanWithLabel rss l) -> do
+ let best_span = (rss, l)
+ let dcMap' = alterUniqMap (maybe (Just ((0, best_span) :| [] ))
+ (\xs@((k, _):|_) -> Just ((k + 1, best_span) `NE.cons` xs))) (provDC env) dc
+ lift $ put (env { provDC = dcMap' })
+ let r = lookupUniqMap dcMap' dc
+ return $ case r of
+ Nothing -> NoNumber
+ Just res -> Numbered (fst (NE.head res))
+
+selectTick :: [Tickish Id] -> Maybe SpanWithLabel
+selectTick [] = Nothing
+selectTick (SourceNote rss d : ts ) = selectTick ts <|> Just (SpanWithLabel rss d)
+selectTick (_:ts) = selectTick ts
+
+{-
+Note [Mapping Info Tables to Source Positions]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+This note describes what the `-finfo-table-map` flag achieves.
+
+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 three parts to the implementation
+
+1. In GHC.Stg.Debug, the SourceNote information is used in order to give a source location to
+some specific closures.
+2. In StgToCmm, the actually used info tables are recorded in an IORef, this
+is important as it's hard to predict beforehand what code generation will do
+and which ids will end up in the generated program.
+3. 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
+
+At the moment thunk and constructor closures are added to the map. This information
+is collected in the `InfoTableProvMap` which provides a mapping from:
+
+1. Data constructors to a list of where they are used.
+2. `Name`s and where they originate from.
+
+During the CoreToStg phase, this map is populated whenever something is turned into
+a StgRhsClosure or an StgConApp. The current source position is recorded
+depending on the location indicated by the surrounding SourceNote.
+
+The functions which add information to the map are `recordStgIdPosition` and
+`numberDataCon`.
+
+When the -fdistinct-constructor-tables` flag is turned on then every
+usage of a data constructor gets its own distinct info table. This is orchestrated
+in `collectExpr` where an incrementing number is used to distinguish each
+occurrence of a data constructor.
+
+-- StgToCmm
+
+The info tables which are actually used in the generated program are recorded during the
+conversion from STG to Cmm. The used info tables are recorded in the `emitProc` function.
+All the used info tables are recorded in the `cgs_used_info` field. This step
+is necessary because when the information about names is collected in the previous
+phase it's unpredictable about which names will end up needing info tables. If
+you don't record which ones are actually used then you end up generating code
+which references info tables which don't exist.
+
+-- Code Generation
+
+The output of these two phases is combined together during code generation.
+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 is created by `ipInitCode` in the same manner as a
+C stub is generated for cost centres.
+
+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 `-fdistinct-info-tables` 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.
+
+-}