module StgCmmProf (
initCostCentres, ccType, ccsType,
mkCCostCentre, mkCCostCentreStack,
dynProfHdr, profDynAlloc, profAlloc, staticProfHdr, initUpdFrameProf,
enterCostCentreThunk, enterCostCentreFun,
costCentreFrom,
curCCS, storeCurCCS,
emitSetCCC,
saveCurrentCostCentre, restoreCurrentCostCentre,
ldvEnter, ldvEnterClosure, ldvRecordCreate
) where
#include "HsVersions.h"
import StgCmmClosure
import StgCmmUtils
import StgCmmMonad
import SMRep
import MkGraph
import Cmm
import CmmUtils
import CLabel
import qualified Module
import CostCentre
import DynFlags
import FastString
import Module
import Outputable
import Control.Monad
import Data.Char (ord)
ccsType :: DynFlags -> CmmType
ccsType = bWord
ccType :: DynFlags -> CmmType
ccType = bWord
curCCS :: CmmExpr
curCCS = CmmReg (CmmGlobal CCCS)
storeCurCCS :: CmmExpr -> CmmAGraph
storeCurCCS e = mkAssign (CmmGlobal CCCS) e
mkCCostCentre :: CostCentre -> CmmLit
mkCCostCentre cc = CmmLabel (mkCCLabel cc)
mkCCostCentreStack :: CostCentreStack -> CmmLit
mkCCostCentreStack ccs = CmmLabel (mkCCSLabel ccs)
costCentreFrom :: DynFlags
-> CmmExpr
-> CmmExpr
costCentreFrom dflags cl = CmmLoad (cmmOffsetB dflags cl (oFFSET_StgHeader_ccs dflags)) (ccsType dflags)
staticProfHdr :: DynFlags -> CostCentreStack -> [CmmLit]
staticProfHdr dflags ccs
= ifProfilingL dflags [mkCCostCentreStack ccs, staticLdvInit dflags]
dynProfHdr :: DynFlags -> CmmExpr -> [CmmExpr]
dynProfHdr dflags ccs = ifProfilingL dflags [ccs, dynLdvInit dflags]
initUpdFrameProf :: CmmExpr -> FCode ()
initUpdFrameProf frame
= ifProfiling $
do dflags <- getDynFlags
emitStore (cmmOffset dflags frame (oFFSET_StgHeader_ccs dflags)) curCCS
saveCurrentCostCentre :: FCode (Maybe LocalReg)
saveCurrentCostCentre
= do dflags <- getDynFlags
if not (gopt Opt_SccProfilingOn dflags)
then return Nothing
else do local_cc <- newTemp (ccType dflags)
emitAssign (CmmLocal local_cc) curCCS
return (Just local_cc)
restoreCurrentCostCentre :: Maybe LocalReg -> FCode ()
restoreCurrentCostCentre Nothing
= return ()
restoreCurrentCostCentre (Just local_cc)
= emit (storeCurCCS (CmmReg (CmmLocal local_cc)))
profDynAlloc :: SMRep -> CmmExpr -> FCode ()
profDynAlloc rep ccs
= ifProfiling $
do dflags <- getDynFlags
profAlloc (mkIntExpr dflags (heapClosureSize dflags rep)) ccs
profAlloc :: CmmExpr -> CmmExpr -> FCode ()
profAlloc words ccs
= ifProfiling $
do dflags <- getDynFlags
let alloc_rep = rEP_CostCentreStack_mem_alloc dflags
emit (addToMemE alloc_rep
(cmmOffsetB dflags ccs (oFFSET_CostCentreStack_mem_alloc dflags))
(CmmMachOp (MO_UU_Conv (wordWidth dflags) (typeWidth alloc_rep)) $
[CmmMachOp (mo_wordSub dflags) [words,
mkIntExpr dflags (profHdrSize dflags)]]))
enterCostCentreThunk :: CmmExpr -> FCode ()
enterCostCentreThunk closure =
ifProfiling $ do
dflags <- getDynFlags
emit $ storeCurCCS (costCentreFrom dflags closure)
enterCostCentreFun :: CostCentreStack -> CmmExpr -> FCode ()
enterCostCentreFun ccs closure =
ifProfiling $ do
if isCurrentCCS ccs
then do dflags <- getDynFlags
emitRtsCall rtsPackageId (fsLit "enterFunCCS")
[(CmmReg (CmmGlobal BaseReg), AddrHint),
(costCentreFrom dflags closure, AddrHint)] False
else return ()
ifProfiling :: FCode () -> FCode ()
ifProfiling code
= do dflags <- getDynFlags
if gopt Opt_SccProfilingOn dflags
then code
else return ()
ifProfilingL :: DynFlags -> [a] -> [a]
ifProfilingL dflags xs
| gopt Opt_SccProfilingOn dflags = xs
| otherwise = []
initCostCentres :: CollectedCCs -> FCode ()
initCostCentres (local_CCs, ___extern_CCs, singleton_CCSs)
= do dflags <- getDynFlags
when (gopt Opt_SccProfilingOn dflags) $
do mapM_ emitCostCentreDecl local_CCs
mapM_ emitCostCentreStackDecl singleton_CCSs
emitCostCentreDecl :: CostCentre -> FCode ()
emitCostCentreDecl cc = do
{ dflags <- getDynFlags
; let is_caf | isCafCC cc = mkIntCLit dflags (ord 'c')
| otherwise = zero dflags
; label <- newByteStringCLit (bytesFS $ costCentreUserNameFS cc)
; modl <- newByteStringCLit (bytesFS $ Module.moduleNameFS
$ Module.moduleName
$ cc_mod cc)
; loc <- newByteStringCLit $ bytesFS $ mkFastString $
showPpr dflags (costCentreSrcSpan cc)
; let
lits = [ zero dflags,
label,
modl,
loc,
zero64,
zero dflags,
is_caf,
zero dflags
]
; emitDataLits (mkCCLabel cc) lits
}
emitCostCentreStackDecl :: CostCentreStack -> FCode ()
emitCostCentreStackDecl ccs
= case maybeSingletonCCS ccs of
Just cc ->
do dflags <- getDynFlags
let mk_lits cc = zero dflags :
mkCCostCentre cc :
replicate (sizeof_ccs_words dflags 2) (zero dflags)
emitDataLits (mkCCSLabel ccs) (mk_lits cc)
Nothing -> pprPanic "emitCostCentreStackDecl" (ppr ccs)
zero :: DynFlags -> CmmLit
zero dflags = mkIntCLit dflags 0
zero64 :: CmmLit
zero64 = CmmInt 0 W64
sizeof_ccs_words :: DynFlags -> Int
sizeof_ccs_words dflags
| ms == 0 = ws
| otherwise = ws + 1
where
(ws,ms) = sIZEOF_CostCentreStack dflags `divMod` wORD_SIZE dflags
emitSetCCC :: CostCentre -> Bool -> Bool -> FCode ()
emitSetCCC cc tick push
= do dflags <- getDynFlags
if not (gopt Opt_SccProfilingOn dflags)
then return ()
else do tmp <- newTemp (ccsType dflags)
pushCostCentre tmp curCCS cc
when tick $ emit (bumpSccCount dflags (CmmReg (CmmLocal tmp)))
when push $ emit (storeCurCCS (CmmReg (CmmLocal tmp)))
pushCostCentre :: LocalReg -> CmmExpr -> CostCentre -> FCode ()
pushCostCentre result ccs cc
= emitRtsCallWithResult result AddrHint
rtsPackageId
(fsLit "pushCostCentre") [(ccs,AddrHint),
(CmmLit (mkCCostCentre cc), AddrHint)]
False
bumpSccCount :: DynFlags -> CmmExpr -> CmmAGraph
bumpSccCount dflags ccs
= addToMem (rEP_CostCentreStack_scc_count dflags)
(cmmOffsetB dflags ccs (oFFSET_CostCentreStack_scc_count dflags)) 1
staticLdvInit :: DynFlags -> CmmLit
staticLdvInit = zeroCLit
dynLdvInit :: DynFlags -> CmmExpr
dynLdvInit dflags =
CmmMachOp (mo_wordOr dflags) [
CmmMachOp (mo_wordShl dflags) [loadEra dflags, mkIntExpr dflags (lDV_SHIFT dflags)],
CmmLit (mkWordCLit dflags (iLDV_STATE_CREATE dflags))
]
ldvRecordCreate :: CmmExpr -> FCode ()
ldvRecordCreate closure = do dflags <- getDynFlags
emit $ mkStore (ldvWord dflags closure) (dynLdvInit dflags)
ldvEnterClosure :: ClosureInfo -> CmmReg -> FCode ()
ldvEnterClosure closure_info node_reg = do
dflags <- getDynFlags
let tag = funTag dflags closure_info
ldvEnter (cmmOffsetB dflags (CmmReg node_reg) (tag))
ldvEnter :: CmmExpr -> FCode ()
ldvEnter cl_ptr = do
dflags <- getDynFlags
let
ldv_wd = ldvWord dflags cl_ptr
new_ldv_wd = cmmOrWord dflags (cmmAndWord dflags (CmmLoad ldv_wd (bWord dflags))
(CmmLit (mkWordCLit dflags (iLDV_CREATE_MASK dflags))))
(cmmOrWord dflags (loadEra dflags) (CmmLit (mkWordCLit dflags (iLDV_STATE_USE dflags))))
ifProfiling $
emit =<< mkCmmIfThenElse (CmmMachOp (mo_wordUGt dflags) [loadEra dflags, CmmLit (zeroCLit dflags)])
(mkStore ldv_wd new_ldv_wd)
mkNop
loadEra :: DynFlags -> CmmExpr
loadEra dflags = CmmMachOp (MO_UU_Conv (cIntWidth dflags) (wordWidth dflags))
[CmmLoad (mkLblExpr (mkCmmDataLabel rtsPackageId (fsLit "era")))
(cInt dflags)]
ldvWord :: DynFlags -> CmmExpr -> CmmExpr
ldvWord dflags closure_ptr
= cmmOffsetB dflags closure_ptr (oFFSET_StgHeader_ldvw dflags)