module GHC.Stg.Debug(collectDebugInformation) where
import GHC.Prelude
import GHC.Stg.Syntax
import GHC.Types.Id
import GHC.Types.Tickish
import GHC.Core.DataCon
import GHC.Types.IPE
import GHC.Unit.Module
import GHC.Types.Name ( getName, getOccName, occNameString, nameSrcSpan)
import GHC.Data.FastString
import GHC.Driver.Session
import Control.Monad (when)
import Control.Monad.Trans.Reader
import Control.Monad.Trans.State
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
data R = R { rDynFlags :: DynFlags, rModLocation :: ModLocation, rSpan :: Maybe SpanWithLabel }
type M a = ReaderT R (State InfoTableProvMap) a
withSpan :: (RealSrcSpan, String) -> M a -> M a
withSpan (new_s, new_l) act = local maybe_replace act
where
maybe_replace r@R{ rModLocation = cur_mod, rSpan = Just (SpanWithLabel old_s _old_l) }
| Just (unpackFS $ srcSpanFile old_s) == ml_hs_file cur_mod
, Just (unpackFS $ srcSpanFile new_s) /= ml_hs_file cur_mod
= r
maybe_replace r
= r { rSpan = Just (SpanWithLabel new_s new_l) }
collectDebugInformation :: DynFlags -> ModLocation -> [StgTopBinding] -> ([StgTopBinding], InfoTableProvMap)
collectDebugInformation dflags ml bs =
runState (runReaderT (mapM collectTop bs) (R dflags ml Nothing)) emptyInfoTableProvMap
collectTop :: StgTopBinding -> M StgTopBinding
collectTop (StgTopLifted t) = StgTopLifted <$> collectStgBind t
collectTop tb = return tb
collectStgBind :: StgBinding -> M StgBinding
collectStgBind (StgNonRec bndr rhs) = do
rhs' <- collectStgRhs bndr rhs
return (StgNonRec bndr rhs')
collectStgBind (StgRec pairs) = do
es <- mapM (\(b, e) -> (b,) <$> collectStgRhs b e) pairs
return (StgRec es)
collectStgRhs :: Id -> StgRhs -> M StgRhs
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 _mn ticks args) = do
n' <- numberDataCon dc ticks
return (StgRhsCon cc dc n' ticks args)
recordInfo :: Id -> StgExpr -> M ()
recordInfo bndr new_rhs = do
modLoc <- asks rModLocation
let
thisFile = maybe nilFS mkFastString $ ml_hs_file modLoc
best_span = quickSourcePos thisFile new_rhs
bndr_span = (\s -> SpanWithLabel s (occNameString (getOccName bndr)))
<$> srcSpanToRealSrcSpan (nameSrcSpan (getName bndr))
recordStgIdPosition bndr best_span bndr_span
collectExpr :: StgExpr -> M StgExpr
collectExpr = go
where
go (StgApp occ as) = return $ StgApp occ as
go (StgLit lit) = return $ StgLit lit
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
go (StgLet ext bind body) = do
bind' <- collectStgBind bind
body' <- go body
return (StgLet ext bind' body')
go (StgLetNoEscape ext bind body) = do
bind' <- collectStgBind bind
body' <- go body
return (StgLetNoEscape ext bind' body')
go (StgTick tick e) = do
let k = case tick of
SourceNote ss fp -> withSpan (ss, fp)
_ -> id
e' <- k (go e)
return (StgTick tick e')
collectAlt :: StgAlt -> M StgAlt
collectAlt (ac, bs, e) = (ac, bs, ) <$> collectExpr e
quickSourcePos :: FastString -> StgExpr -> Maybe SpanWithLabel
quickSourcePos cur_mod (StgTick (SourceNote ss m) e)
| srcSpanFile ss == cur_mod = Just (SpanWithLabel ss m)
| otherwise = quickSourcePos cur_mod e
quickSourcePos _ _ = Nothing
recordStgIdPosition :: Id -> Maybe SpanWithLabel -> Maybe SpanWithLabel -> M ()
recordStgIdPosition id best_span ss = do
dflags <- asks rDynFlags
when (gopt Opt_InfoTableMap dflags) $ do
cc <- asks rSpan
let mbspan = (\(SpanWithLabel rss d) -> (rss, d)) <$> (best_span <|> cc <|> ss)
lift $ modify (\env -> env { provClosure = addToUniqMap (provClosure env) (idName id) (idType id, mbspan) })
numberDataCon :: DataCon -> [StgTickish] -> M ConstructorNumber
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 = (\(SpanWithLabel rss l) -> (rss, l)) <$> (selectTick ts <|> mcc)
let dcMap' = alterUniqMap (maybe (Just ((0, mbest_span) :| [] ))
(\xs@((k, _):|_) -> Just ((k + 1, mbest_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 :: [StgTickish] -> Maybe SpanWithLabel
selectTick [] = Nothing
selectTick (SourceNote rss d : ts ) = selectTick ts <|> Just (SpanWithLabel rss d)
selectTick (_:ts) = selectTick ts