module GHC.StgToCmm.Prof (
initCostCentres, ccType, ccsType,
mkCCostCentre, mkCCostCentreStack,
dynProfHdr, profDynAlloc, profAlloc, staticProfHdr, initUpdFrameProf,
enterCostCentreThunk, enterCostCentreFun,
costCentreFrom,
storeCurCCS,
emitSetCCC,
saveCurrentCostCentre, restoreCurrentCostCentre,
ldvEnter, ldvEnterClosure, ldvRecordCreate
) where
import GHC.Prelude
import GHC.Platform
import GHC.StgToCmm.Closure
import GHC.StgToCmm.Utils
import GHC.StgToCmm.Monad
import GHC.Runtime.Heap.Layout
import GHC.Cmm.Graph
import GHC.Cmm
import GHC.Cmm.Utils
import GHC.Cmm.CLabel
import GHC.Types.CostCentre
import GHC.Driver.Session
import GHC.Data.FastString
import GHC.Unit.Module as Module
import GHC.Utils.Outputable
import Control.Monad
import Data.Char (ord)
ccsType :: Platform -> CmmType
ccsType = bWord
ccType :: Platform -> CmmType
ccType = bWord
storeCurCCS :: CmmExpr -> CmmAGraph
storeCurCCS e = mkAssign cccsReg 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 platform cl (oFFSET_StgHeader_ccs dflags)) (ccsType platform)
where platform = targetPlatform dflags
staticProfHdr :: DynFlags -> CostCentreStack -> [CmmLit]
staticProfHdr dflags ccs
| sccProfilingEnabled dflags = [mkCCostCentreStack ccs, staticLdvInit platform]
| otherwise = []
where platform = targetPlatform dflags
dynProfHdr :: DynFlags -> CmmExpr -> [CmmExpr]
dynProfHdr dflags ccs
| sccProfilingEnabled dflags = [ccs, dynLdvInit dflags]
| otherwise = []
initUpdFrameProf :: CmmExpr -> FCode ()
initUpdFrameProf frame
= ifProfiling $
do dflags <- getDynFlags
platform <- getPlatform
emitStore (cmmOffset platform frame (oFFSET_StgHeader_ccs dflags)) cccsExpr
saveCurrentCostCentre :: FCode (Maybe LocalReg)
saveCurrentCostCentre
= do dflags <- getDynFlags
platform <- getPlatform
if not (sccProfilingEnabled dflags)
then return Nothing
else do local_cc <- newTemp (ccType platform)
emitAssign (CmmLocal local_cc) cccsExpr
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
platform <- getPlatform
profAlloc (mkIntExpr platform (heapClosureSizeW dflags rep)) ccs
profAlloc :: CmmExpr -> CmmExpr -> FCode ()
profAlloc words ccs
= ifProfiling $
do dflags <- getDynFlags
platform <- getPlatform
let alloc_rep = rEP_CostCentreStack_mem_alloc dflags
emit (addToMemE alloc_rep
(cmmOffsetB platform ccs (oFFSET_CostCentreStack_mem_alloc dflags))
(CmmMachOp (MO_UU_Conv (wordWidth platform) (typeWidth alloc_rep)) $
[CmmMachOp (mo_wordSub platform) [words,
mkIntExpr platform (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 rtsUnitId (fsLit "enterFunCCS")
[(baseExpr, AddrHint),
(costCentreFrom dflags closure, AddrHint)] False
else return ()
ifProfiling :: FCode () -> FCode ()
ifProfiling code
= do dflags <- getDynFlags
if sccProfilingEnabled dflags
then code
else return ()
initCostCentres :: CollectedCCs -> FCode ()
initCostCentres (local_CCs, singleton_CCSs)
= do dflags <- getDynFlags
when (sccProfilingEnabled dflags) $
do mapM_ emitCostCentreDecl local_CCs
mapM_ emitCostCentreStackDecl singleton_CCSs
emitCostCentreDecl :: CostCentre -> FCode ()
emitCostCentreDecl cc = do
{ dflags <- getDynFlags
; platform <- getPlatform
; let is_caf | isCafCC cc = mkIntCLit platform (ord 'c')
| otherwise = zero platform
; label <- newByteStringCLit (bytesFS $ costCentreUserNameFS cc)
; modl <- newByteStringCLit (bytesFS $ moduleNameFS
$ moduleName
$ cc_mod cc)
; loc <- newByteStringCLit $ bytesFS $ mkFastString $
showPpr dflags (costCentreSrcSpan cc)
; let
lits = [ zero platform,
label,
modl,
loc,
zero64,
zero platform,
is_caf,
zero platform
]
; emitDataLits (mkCCLabel cc) lits
}
emitCostCentreStackDecl :: CostCentreStack -> FCode ()
emitCostCentreStackDecl ccs
= case maybeSingletonCCS ccs of
Just cc ->
do dflags <- getDynFlags
platform <- getPlatform
let mk_lits cc = zero platform :
mkCCostCentre cc :
replicate (sizeof_ccs_words dflags 2) (zero platform)
emitDataLits (mkCCSLabel ccs) (mk_lits cc)
Nothing -> pprPanic "emitCostCentreStackDecl" (ppr ccs)
zero :: Platform -> CmmLit
zero platform = mkIntCLit platform 0
zero64 :: CmmLit
zero64 = CmmInt 0 W64
sizeof_ccs_words :: DynFlags -> Int
sizeof_ccs_words dflags
| ms == 0 = ws
| otherwise = ws + 1
where
platform = targetPlatform dflags
(ws,ms) = sIZEOF_CostCentreStack dflags `divMod` platformWordSizeInBytes platform
emitSetCCC :: CostCentre -> Bool -> Bool -> FCode ()
emitSetCCC cc tick push
= do dflags <- getDynFlags
platform <- getPlatform
if not (sccProfilingEnabled dflags)
then return ()
else do tmp <- newTemp (ccsType platform)
pushCostCentre tmp cccsExpr 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
rtsUnitId
(fsLit "pushCostCentre") [(ccs,AddrHint),
(CmmLit (mkCCostCentre cc), AddrHint)]
False
bumpSccCount :: DynFlags -> CmmExpr -> CmmAGraph
bumpSccCount dflags ccs
= addToMem (rEP_CostCentreStack_scc_count dflags)
(cmmOffsetB platform ccs (oFFSET_CostCentreStack_scc_count dflags)) 1
where platform = targetPlatform dflags
staticLdvInit :: Platform -> CmmLit
staticLdvInit = zeroCLit
dynLdvInit :: DynFlags -> CmmExpr
dynLdvInit dflags =
CmmMachOp (mo_wordOr platform) [
CmmMachOp (mo_wordShl platform) [loadEra dflags, mkIntExpr platform (lDV_SHIFT dflags)],
CmmLit (mkWordCLit platform (iLDV_STATE_CREATE dflags))
]
where
platform = targetPlatform 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
platform <- getPlatform
let tag = funTag dflags closure_info
ldvEnter (cmmOffsetB platform (CmmReg node_reg) (tag))
ldvEnter :: CmmExpr -> FCode ()
ldvEnter cl_ptr = do
dflags <- getDynFlags
platform <- getPlatform
let
ldv_wd = ldvWord dflags cl_ptr
new_ldv_wd = cmmOrWord platform
(cmmAndWord platform (CmmLoad ldv_wd (bWord platform))
(CmmLit (mkWordCLit platform (iLDV_CREATE_MASK dflags))))
(cmmOrWord platform (loadEra dflags) (CmmLit (mkWordCLit platform (iLDV_STATE_USE dflags))))
ifProfiling $
emit =<< mkCmmIfThenElse (CmmMachOp (mo_wordUGt platform) [loadEra dflags, CmmLit (zeroCLit platform)])
(mkStore ldv_wd new_ldv_wd)
mkNop
loadEra :: DynFlags -> CmmExpr
loadEra dflags = CmmMachOp (MO_UU_Conv (cIntWidth dflags) (wordWidth platform))
[CmmLoad (mkLblExpr (mkRtsCmmDataLabel (fsLit "era")))
(cInt dflags)]
where platform = targetPlatform dflags
ldvWord :: DynFlags -> CmmExpr -> CmmExpr
ldvWord dflags closure_ptr
= cmmOffsetB platform closure_ptr (oFFSET_StgHeader_ldvw dflags)
where platform = targetPlatform dflags