{-# LANGUAGE BangPatterns #-}
module StgCmmTicky (
withNewTickyCounterFun,
withNewTickyCounterLNE,
withNewTickyCounterThunk,
withNewTickyCounterStdThunk,
withNewTickyCounterCon,
tickyDynAlloc,
tickyAllocHeap,
tickyAllocPrim,
tickyAllocThunk,
tickyAllocPAP,
tickyHeapCheck,
tickyStackCheck,
tickyUnknownCall, tickyDirectCall,
tickyPushUpdateFrame,
tickyUpdateFrameOmitted,
tickyEnterDynCon,
tickyEnterStaticCon,
tickyEnterViaNode,
tickyEnterFun,
tickyEnterThunk, tickyEnterStdThunk,
tickyEnterLNE,
tickyUpdateBhCaf,
tickyBlackHole,
tickyUnboxedTupleReturn,
tickyReturnOldCon, tickyReturnNewCon,
tickyKnownCallTooFewArgs, tickyKnownCallExact, tickyKnownCallExtraArgs,
tickySlowCall, tickySlowCallPat,
) where
import GhcPrelude
import StgCmmArgRep ( slowCallPattern , toArgRep , argRepString )
import StgCmmClosure
import StgCmmUtils
import StgCmmMonad
import StgSyn
import CmmExpr
import MkGraph
import CmmUtils
import CLabel
import SMRep
import Module
import Name
import Id
import BasicTypes
import FastString
import Outputable
import Util
import DynFlags
import PrelNames
import TcType
import Type
import TyCon
import Data.Maybe
import qualified Data.Char
import Control.Monad ( when )
data TickyClosureType
= TickyFun
Bool
| TickyCon
| TickyThunk
Bool
Bool
| TickyLNE
withNewTickyCounterFun :: Bool -> Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounterFun :: Bool -> Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounterFun single_entry :: Bool
single_entry = TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
forall a.
TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounter (Bool -> TickyClosureType
TickyFun Bool
single_entry)
withNewTickyCounterLNE :: Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounterLNE :: Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounterLNE nm :: Name
nm args :: [NonVoid Id]
args code :: FCode a
code = do
Bool
b <- FCode Bool
tickyLNEIsOn
if Bool -> Bool
not Bool
b then FCode a
code else TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
forall a.
TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounter TickyClosureType
TickyLNE Name
nm [NonVoid Id]
args FCode a
code
thunkHasCounter :: Bool -> FCode Bool
thunkHasCounter :: Bool -> FCode Bool
thunkHasCounter isStatic :: Bool
isStatic = do
Bool
b <- FCode Bool
tickyDynThunkIsOn
Bool -> FCode Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Bool
not Bool
isStatic Bool -> Bool -> Bool
&& Bool
b)
withNewTickyCounterThunk
:: Bool
-> Bool
-> Name
-> FCode a
-> FCode a
withNewTickyCounterThunk :: Bool -> Bool -> Name -> FCode a -> FCode a
withNewTickyCounterThunk isStatic :: Bool
isStatic isUpdatable :: Bool
isUpdatable name :: Name
name code :: FCode a
code = do
Bool
has_ctr <- Bool -> FCode Bool
thunkHasCounter Bool
isStatic
if Bool -> Bool
not Bool
has_ctr
then FCode a
code
else TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
forall a.
TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounter (Bool -> Bool -> TickyClosureType
TickyThunk Bool
isUpdatable Bool
False) Name
name [] FCode a
code
withNewTickyCounterStdThunk
:: Bool
-> Name
-> FCode a
-> FCode a
withNewTickyCounterStdThunk :: Bool -> Name -> FCode a -> FCode a
withNewTickyCounterStdThunk isUpdatable :: Bool
isUpdatable name :: Name
name code :: FCode a
code = do
Bool
has_ctr <- Bool -> FCode Bool
thunkHasCounter Bool
False
if Bool -> Bool
not Bool
has_ctr
then FCode a
code
else TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
forall a.
TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounter (Bool -> Bool -> TickyClosureType
TickyThunk Bool
isUpdatable Bool
True) Name
name [] FCode a
code
withNewTickyCounterCon
:: Name
-> FCode a
-> FCode a
withNewTickyCounterCon :: Name -> FCode a -> FCode a
withNewTickyCounterCon name :: Name
name code :: FCode a
code = do
Bool
has_ctr <- Bool -> FCode Bool
thunkHasCounter Bool
False
if Bool -> Bool
not Bool
has_ctr
then FCode a
code
else TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
forall a.
TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounter TickyClosureType
TickyCon Name
name [] FCode a
code
withNewTickyCounter :: TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounter :: TickyClosureType -> Name -> [NonVoid Id] -> FCode a -> FCode a
withNewTickyCounter cloType :: TickyClosureType
cloType name :: Name
name args :: [NonVoid Id]
args m :: FCode a
m = do
CLabel
lbl <- TickyClosureType -> Name -> [NonVoid Id] -> FCode CLabel
emitTickyCounter TickyClosureType
cloType Name
name [NonVoid Id]
args
CLabel -> FCode a -> FCode a
forall a. CLabel -> FCode a -> FCode a
setTickyCtrLabel CLabel
lbl FCode a
m
emitTickyCounter :: TickyClosureType -> Name -> [NonVoid Id] -> FCode CLabel
emitTickyCounter :: TickyClosureType -> Name -> [NonVoid Id] -> FCode CLabel
emitTickyCounter cloType :: TickyClosureType
cloType name :: Name
name args :: [NonVoid Id]
args
= let ctr_lbl :: CLabel
ctr_lbl = Name -> CLabel
mkRednCountsLabel Name
name in
(FCode () -> FCode CLabel -> FCode CLabel
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CLabel -> FCode CLabel
forall (m :: * -> *) a. Monad m => a -> m a
return CLabel
ctr_lbl) (FCode () -> FCode CLabel) -> FCode () -> FCode CLabel
forall a b. (a -> b) -> a -> b
$
FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do
{ DynFlags
dflags <- FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
; CLabel
parent <- FCode CLabel
getTickyCtrLabel
; Module
mod_name <- FCode Module
getModuleName
; let ppr_for_ticky_name :: SDoc
ppr_for_ticky_name :: SDoc
ppr_for_ticky_name =
let n :: SDoc
n = Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr Name
name
ext :: SDoc
ext = case TickyClosureType
cloType of
TickyFun single_entry :: Bool
single_entry -> SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
hcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ([SDoc] -> [SDoc]) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$
[String -> SDoc
text "fun"] [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++ [String -> SDoc
text "se"|Bool
single_entry]
TickyCon -> SDoc -> SDoc
parens (String -> SDoc
text "con")
TickyThunk upd :: Bool
upd std :: Bool
std -> SDoc -> SDoc
parens (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
hcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ SDoc -> [SDoc] -> [SDoc]
punctuate SDoc
comma ([SDoc] -> [SDoc]) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> a -> b
$
[String -> SDoc
text "thk"] [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++ [String -> SDoc
text "se"|Bool -> Bool
not Bool
upd] [SDoc] -> [SDoc] -> [SDoc]
forall a. [a] -> [a] -> [a]
++ [String -> SDoc
text "std"|Bool
std]
TickyLNE | Name -> Bool
isInternalName Name
name -> SDoc -> SDoc
parens (String -> SDoc
text "LNE")
| Bool
otherwise -> String -> SDoc
forall a. String -> a
panic "emitTickyCounter: how is this an external LNE?"
p :: SDoc
p = case CLabel -> Maybe Name
hasHaskellName CLabel
parent of
Just pname :: Name
pname -> String -> SDoc
text "in" SDoc -> SDoc -> SDoc
<+> Unique -> SDoc
forall a. Outputable a => a -> SDoc
ppr (Name -> Unique
nameUnique Name
pname)
_ -> SDoc
empty
in if Name -> Bool
isInternalName Name
name
then SDoc
n SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
parens (Module -> SDoc
forall a. Outputable a => a -> SDoc
ppr Module
mod_name) SDoc -> SDoc -> SDoc
<+> SDoc
ext SDoc -> SDoc -> SDoc
<+> SDoc
p
else SDoc
n SDoc -> SDoc -> SDoc
<+> SDoc
ext SDoc -> SDoc -> SDoc
<+> SDoc
p
; CmmLit
fun_descr_lit <- String -> FCode CmmLit
newStringCLit (String -> FCode CmmLit) -> String -> FCode CmmLit
forall a b. (a -> b) -> a -> b
$ DynFlags -> SDoc -> String
showSDocDebug DynFlags
dflags SDoc
ppr_for_ticky_name
; CmmLit
arg_descr_lit <- String -> FCode CmmLit
newStringCLit (String -> FCode CmmLit) -> String -> FCode CmmLit
forall a b. (a -> b) -> a -> b
$ (NonVoid Id -> Char) -> [NonVoid Id] -> String
forall a b. (a -> b) -> [a] -> [b]
map (Type -> Char
showTypeCategory (Type -> Char) -> (NonVoid Id -> Type) -> NonVoid Id -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Id -> Type
idType (Id -> Type) -> (NonVoid Id -> Id) -> NonVoid Id -> Type
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonVoid Id -> Id
forall a. NonVoid a -> a
fromNonVoid) [NonVoid Id]
args
; CLabel -> [CmmLit] -> FCode ()
emitDataLits CLabel
ctr_lbl
[ DynFlags -> Int -> CmmLit
mkIntCLit DynFlags
dflags 0,
DynFlags -> Int -> CmmLit
mkIntCLit DynFlags
dflags ([NonVoid Id] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [NonVoid Id]
args),
DynFlags -> Int -> CmmLit
mkIntCLit DynFlags
dflags 0,
CmmLit
fun_descr_lit,
CmmLit
arg_descr_lit,
DynFlags -> CmmLit
zeroCLit DynFlags
dflags,
DynFlags -> CmmLit
zeroCLit DynFlags
dflags,
DynFlags -> CmmLit
zeroCLit DynFlags
dflags
]
}
tickyPushUpdateFrame, tickyUpdateFrameOmitted :: FCode ()
tickyPushUpdateFrame :: FCode ()
tickyPushUpdateFrame = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "UPDF_PUSHED_ctr")
tickyUpdateFrameOmitted :: FCode ()
tickyUpdateFrameOmitted = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "UPDF_OMITTED_ctr")
tickyEnterDynCon, tickyEnterStaticCon, tickyEnterViaNode :: FCode ()
tickyEnterDynCon :: FCode ()
tickyEnterDynCon = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "ENT_DYN_CON_ctr")
tickyEnterStaticCon :: FCode ()
tickyEnterStaticCon = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "ENT_STATIC_CON_ctr")
tickyEnterViaNode :: FCode ()
tickyEnterViaNode = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "ENT_VIA_NODE_ctr")
tickyEnterThunk :: ClosureInfo -> FCode ()
tickyEnterThunk :: ClosureInfo -> FCode ()
tickyEnterThunk cl_info :: ClosureInfo
cl_info
= FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do
{ FastString -> FCode ()
bumpTickyCounter FastString
ctr
; Bool
has_ctr <- Bool -> FCode Bool
thunkHasCounter Bool
static
; Bool -> FCode () -> FCode ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
has_ctr (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do
CLabel
ticky_ctr_lbl <- FCode CLabel
getTickyCtrLabel
CLabel -> FCode ()
registerTickyCtrAtEntryDyn CLabel
ticky_ctr_lbl
CLabel -> FCode ()
bumpTickyEntryCount CLabel
ticky_ctr_lbl }
where
updatable :: Bool
updatable = ClosureInfo -> Bool
closureSingleEntry ClosureInfo
cl_info
static :: Bool
static = ClosureInfo -> Bool
isStaticClosure ClosureInfo
cl_info
ctr :: FastString
ctr | Bool
static = if Bool
updatable then String -> FastString
fsLit "ENT_STATIC_THK_SINGLE_ctr"
else String -> FastString
fsLit "ENT_STATIC_THK_MANY_ctr"
| Bool
otherwise = if Bool
updatable then String -> FastString
fsLit "ENT_DYN_THK_SINGLE_ctr"
else String -> FastString
fsLit "ENT_DYN_THK_MANY_ctr"
tickyEnterStdThunk :: ClosureInfo -> FCode ()
tickyEnterStdThunk :: ClosureInfo -> FCode ()
tickyEnterStdThunk = ClosureInfo -> FCode ()
tickyEnterThunk
tickyBlackHole :: Bool -> FCode ()
tickyBlackHole :: Bool -> FCode ()
tickyBlackHole updatable :: Bool
updatable
= FCode () -> FCode ()
ifTicky (FastString -> FCode ()
bumpTickyCounter FastString
ctr)
where
ctr :: FastString
ctr | Bool
updatable = (String -> FastString
fsLit "UPD_BH_SINGLE_ENTRY_ctr")
| Bool
otherwise = (String -> FastString
fsLit "UPD_BH_UPDATABLE_ctr")
tickyUpdateBhCaf :: ClosureInfo -> FCode ()
tickyUpdateBhCaf :: ClosureInfo -> FCode ()
tickyUpdateBhCaf cl_info :: ClosureInfo
cl_info
= FCode () -> FCode ()
ifTicky (FastString -> FCode ()
bumpTickyCounter FastString
ctr)
where
ctr :: FastString
ctr | ClosureInfo -> Bool
closureUpdReqd ClosureInfo
cl_info = (String -> FastString
fsLit "UPD_CAF_BH_SINGLE_ENTRY_ctr")
| Bool
otherwise = (String -> FastString
fsLit "UPD_CAF_BH_UPDATABLE_ctr")
tickyEnterFun :: ClosureInfo -> FCode ()
tickyEnterFun :: ClosureInfo -> FCode ()
tickyEnterFun cl_info :: ClosureInfo
cl_info = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do
CLabel
ctr_lbl <- FCode CLabel
getTickyCtrLabel
if ClosureInfo -> Bool
isStaticClosure ClosureInfo
cl_info
then do FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "ENT_STATIC_FUN_DIRECT_ctr")
CLabel -> FCode ()
registerTickyCtr CLabel
ctr_lbl
else do FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "ENT_DYN_FUN_DIRECT_ctr")
CLabel -> FCode ()
registerTickyCtrAtEntryDyn CLabel
ctr_lbl
CLabel -> FCode ()
bumpTickyEntryCount CLabel
ctr_lbl
tickyEnterLNE :: FCode ()
tickyEnterLNE :: FCode ()
tickyEnterLNE = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do
FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "ENT_LNE_ctr")
FCode () -> FCode ()
ifTickyLNE (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do
CLabel
ctr_lbl <- FCode CLabel
getTickyCtrLabel
CLabel -> FCode ()
registerTickyCtr CLabel
ctr_lbl
CLabel -> FCode ()
bumpTickyEntryCount CLabel
ctr_lbl
registerTickyCtrAtEntryDyn :: CLabel -> FCode ()
registerTickyCtrAtEntryDyn :: CLabel -> FCode ()
registerTickyCtrAtEntryDyn ctr_lbl :: CLabel
ctr_lbl = do
Bool
already_registered <- FCode Bool
tickyAllocdIsOn
Bool -> FCode () -> FCode ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
already_registered) (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ CLabel -> FCode ()
registerTickyCtr CLabel
ctr_lbl
registerTickyCtr :: CLabel -> FCode ()
registerTickyCtr :: CLabel -> FCode ()
registerTickyCtr ctr_lbl :: CLabel
ctr_lbl = do
DynFlags
dflags <- FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
let
test :: CmmExpr
test = MachOp -> [CmmExpr] -> CmmExpr
CmmMachOp (Width -> MachOp
MO_Eq (DynFlags -> Width
wordWidth DynFlags
dflags))
[CmmExpr -> CmmType -> CmmExpr
CmmLoad (CmmLit -> CmmExpr
CmmLit (CLabel -> Int -> CmmLit
cmmLabelOffB CLabel
ctr_lbl
(DynFlags -> Int
oFFSET_StgEntCounter_registeredp DynFlags
dflags))) (DynFlags -> CmmType
bWord DynFlags
dflags),
DynFlags -> CmmExpr
zeroExpr DynFlags
dflags]
register_stmts :: [CmmAGraph]
register_stmts
= [ CmmExpr -> CmmExpr -> CmmAGraph
mkStore (CmmLit -> CmmExpr
CmmLit (CLabel -> Int -> CmmLit
cmmLabelOffB CLabel
ctr_lbl (DynFlags -> Int
oFFSET_StgEntCounter_link DynFlags
dflags)))
(CmmExpr -> CmmType -> CmmExpr
CmmLoad CmmExpr
ticky_entry_ctrs (DynFlags -> CmmType
bWord DynFlags
dflags))
, CmmExpr -> CmmExpr -> CmmAGraph
mkStore CmmExpr
ticky_entry_ctrs (CLabel -> CmmExpr
mkLblExpr CLabel
ctr_lbl)
, CmmExpr -> CmmExpr -> CmmAGraph
mkStore (CmmLit -> CmmExpr
CmmLit (CLabel -> Int -> CmmLit
cmmLabelOffB CLabel
ctr_lbl
(DynFlags -> Int
oFFSET_StgEntCounter_registeredp DynFlags
dflags)))
(DynFlags -> Int -> CmmExpr
mkIntExpr DynFlags
dflags 1) ]
ticky_entry_ctrs :: CmmExpr
ticky_entry_ctrs = CLabel -> CmmExpr
mkLblExpr (UnitId -> FastString -> CLabel
mkCmmDataLabel UnitId
rtsUnitId (String -> FastString
fsLit "ticky_entry_ctrs"))
CmmAGraph -> FCode ()
emit (CmmAGraph -> FCode ()) -> FCode CmmAGraph -> FCode ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< CmmExpr -> CmmAGraph -> FCode CmmAGraph
mkCmmIfThen CmmExpr
test ([CmmAGraph] -> CmmAGraph
catAGraphs [CmmAGraph]
register_stmts)
tickyReturnOldCon, tickyReturnNewCon :: RepArity -> FCode ()
tickyReturnOldCon :: Int -> FCode ()
tickyReturnOldCon arity :: Int
arity
= FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do { FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "RET_OLD_ctr")
; FastString -> Int -> FCode ()
bumpHistogram (String -> FastString
fsLit "RET_OLD_hst") Int
arity }
tickyReturnNewCon :: Int -> FCode ()
tickyReturnNewCon arity :: Int
arity
= FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do { FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "RET_NEW_ctr")
; FastString -> Int -> FCode ()
bumpHistogram (String -> FastString
fsLit "RET_NEW_hst") Int
arity }
tickyUnboxedTupleReturn :: RepArity -> FCode ()
tickyUnboxedTupleReturn :: Int -> FCode ()
tickyUnboxedTupleReturn arity :: Int
arity
= FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do { FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "RET_UNBOXED_TUP_ctr")
; FastString -> Int -> FCode ()
bumpHistogram (String -> FastString
fsLit "RET_UNBOXED_TUP_hst") Int
arity }
tickyDirectCall :: RepArity -> [StgArg] -> FCode ()
tickyDirectCall :: Int -> [StgArg] -> FCode ()
tickyDirectCall arity :: Int
arity args :: [StgArg]
args
| [StgArg]
args [StgArg] -> Int -> Bool
forall a. [a] -> Int -> Bool
`lengthIs` Int
arity = FCode ()
tickyKnownCallExact
| Bool
otherwise = do FCode ()
tickyKnownCallExtraArgs
[PrimRep] -> FCode ()
tickySlowCallPat ((StgArg -> PrimRep) -> [StgArg] -> [PrimRep]
forall a b. (a -> b) -> [a] -> [b]
map StgArg -> PrimRep
argPrimRep (Int -> [StgArg] -> [StgArg]
forall a. Int -> [a] -> [a]
drop Int
arity [StgArg]
args))
tickyKnownCallTooFewArgs :: FCode ()
tickyKnownCallTooFewArgs :: FCode ()
tickyKnownCallTooFewArgs = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "KNOWN_CALL_TOO_FEW_ARGS_ctr")
tickyKnownCallExact :: FCode ()
tickyKnownCallExact :: FCode ()
tickyKnownCallExact = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "KNOWN_CALL_ctr")
tickyKnownCallExtraArgs :: FCode ()
= FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "KNOWN_CALL_EXTRA_ARGS_ctr")
tickyUnknownCall :: FCode ()
tickyUnknownCall :: FCode ()
tickyUnknownCall = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "UNKNOWN_CALL_ctr")
tickySlowCall :: LambdaFormInfo -> [StgArg] -> FCode ()
tickySlowCall :: LambdaFormInfo -> [StgArg] -> FCode ()
tickySlowCall _ [] = () -> FCode ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
tickySlowCall lf_info :: LambdaFormInfo
lf_info args :: [StgArg]
args = do
if LambdaFormInfo -> Bool
isKnownFun LambdaFormInfo
lf_info
then FCode ()
tickyKnownCallTooFewArgs
else FCode ()
tickyUnknownCall
[PrimRep] -> FCode ()
tickySlowCallPat ((StgArg -> PrimRep) -> [StgArg] -> [PrimRep]
forall a b. (a -> b) -> [a] -> [b]
map StgArg -> PrimRep
argPrimRep [StgArg]
args)
tickySlowCallPat :: [PrimRep] -> FCode ()
tickySlowCallPat :: [PrimRep] -> FCode ()
tickySlowCallPat args :: [PrimRep]
args = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$
let argReps :: [ArgRep]
argReps = (PrimRep -> ArgRep) -> [PrimRep] -> [ArgRep]
forall a b. (a -> b) -> [a] -> [b]
map PrimRep -> ArgRep
toArgRep [PrimRep]
args
(_, n_matched :: Int
n_matched) = [ArgRep] -> (FastString, Int)
slowCallPattern [ArgRep]
argReps
in if Int
n_matched Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 0 Bool -> Bool -> Bool
&& [PrimRep]
args [PrimRep] -> Int -> Bool
forall a. [a] -> Int -> Bool
`lengthIs` Int
n_matched
then CLabel -> FCode ()
bumpTickyLbl (CLabel -> FCode ()) -> CLabel -> FCode ()
forall a b. (a -> b) -> a -> b
$ String -> CLabel
mkRtsSlowFastTickyCtrLabel (String -> CLabel) -> String -> CLabel
forall a b. (a -> b) -> a -> b
$ (ArgRep -> String) -> [ArgRep] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
Data.Char.toLower (String -> String) -> (ArgRep -> String) -> ArgRep -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArgRep -> String
argRepString) [ArgRep]
argReps
else FastString -> FCode ()
bumpTickyCounter (FastString -> FCode ()) -> FastString -> FCode ()
forall a b. (a -> b) -> a -> b
$ String -> FastString
fsLit "VERY_SLOW_CALL_ctr"
tickyDynAlloc :: Maybe Id -> SMRep -> LambdaFormInfo -> FCode ()
tickyDynAlloc :: Maybe Id -> SMRep -> LambdaFormInfo -> FCode ()
tickyDynAlloc mb_id :: Maybe Id
mb_id rep :: SMRep
rep lf :: LambdaFormInfo
lf = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags FCode DynFlags -> (DynFlags -> FCode ()) -> FCode ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \dflags :: DynFlags
dflags ->
let bytes :: Int
bytes = DynFlags -> Int
wORD_SIZE DynFlags
dflags Int -> Int -> Int
forall a. Num a => a -> a -> a
* DynFlags -> SMRep -> Int
heapClosureSizeW DynFlags
dflags SMRep
rep
countGlobal :: FastString -> FastString -> FCode ()
countGlobal tot :: FastString
tot ctr :: FastString
ctr = do
FastString -> Int -> FCode ()
bumpTickyCounterBy FastString
tot Int
bytes
FastString -> FCode ()
bumpTickyCounter FastString
ctr
countSpecific :: FCode ()
countSpecific = FCode () -> FCode ()
ifTickyAllocd (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ case Maybe Id
mb_id of
Nothing -> () -> FCode ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just id :: Id
id -> do
let ctr_lbl :: CLabel
ctr_lbl = Name -> CLabel
mkRednCountsLabel (Id -> Name
idName Id
id)
CLabel -> FCode ()
registerTickyCtr CLabel
ctr_lbl
CLabel -> Int -> FCode ()
bumpTickyAllocd CLabel
ctr_lbl Int
bytes
in case () of
_ | SMRep -> Bool
isConRep SMRep
rep ->
FCode () -> FCode ()
ifTickyDynThunk FCode ()
countSpecific FCode () -> FCode () -> FCode ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
FastString -> FastString -> FCode ()
countGlobal (String -> FastString
fsLit "ALLOC_CON_gds") (String -> FastString
fsLit "ALLOC_CON_ctr")
| SMRep -> Bool
isThunkRep SMRep
rep ->
FCode () -> FCode ()
ifTickyDynThunk FCode ()
countSpecific FCode () -> FCode () -> FCode ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
if LambdaFormInfo -> Bool
lfUpdatable LambdaFormInfo
lf
then FastString -> FastString -> FCode ()
countGlobal (String -> FastString
fsLit "ALLOC_THK_gds") (String -> FastString
fsLit "ALLOC_UP_THK_ctr")
else FastString -> FastString -> FCode ()
countGlobal (String -> FastString
fsLit "ALLOC_THK_gds") (String -> FastString
fsLit "ALLOC_SE_THK_ctr")
| SMRep -> Bool
isFunRep SMRep
rep ->
FCode ()
countSpecific FCode () -> FCode () -> FCode ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
FastString -> FastString -> FCode ()
countGlobal (String -> FastString
fsLit "ALLOC_FUN_gds") (String -> FastString
fsLit "ALLOC_FUN_ctr")
| Bool
otherwise -> String -> FCode ()
forall a. String -> a
panic "How is this heap object not a con, thunk, or fun?"
tickyAllocHeap ::
Bool ->
VirtualHpOffset -> FCode ()
tickyAllocHeap :: Bool -> Int -> FCode ()
tickyAllocHeap genuine :: Bool
genuine hp :: Int
hp
= FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$
do { DynFlags
dflags <- FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
; CLabel
ticky_ctr <- FCode CLabel
getTickyCtrLabel
; CmmAGraph -> FCode ()
emit (CmmAGraph -> FCode ()) -> CmmAGraph -> FCode ()
forall a b. (a -> b) -> a -> b
$ [CmmAGraph] -> CmmAGraph
catAGraphs ([CmmAGraph] -> CmmAGraph) -> [CmmAGraph] -> CmmAGraph
forall a b. (a -> b) -> a -> b
$
if Int
hp Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0 then []
else let !bytes :: Int
bytes = DynFlags -> Int
wORD_SIZE DynFlags
dflags Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
hp in [
CmmType -> CmmExpr -> Int -> CmmAGraph
addToMem (DynFlags -> CmmType
rEP_StgEntCounter_allocs DynFlags
dflags)
(CmmLit -> CmmExpr
CmmLit (CLabel -> Int -> CmmLit
cmmLabelOffB CLabel
ticky_ctr (DynFlags -> Int
oFFSET_StgEntCounter_allocs DynFlags
dflags)))
Int
bytes,
CmmType -> CLabel -> Int -> CmmAGraph
addToMemLbl (DynFlags -> CmmType
bWord DynFlags
dflags)
(UnitId -> FastString -> CLabel
mkCmmDataLabel UnitId
rtsUnitId (String -> FastString
fsLit "ALLOC_HEAP_tot"))
Int
bytes,
if Bool -> Bool
not Bool
genuine then CmmAGraph
mkNop
else CmmType -> CLabel -> Int -> CmmAGraph
addToMemLbl (DynFlags -> CmmType
bWord DynFlags
dflags)
(UnitId -> FastString -> CLabel
mkCmmDataLabel UnitId
rtsUnitId (String -> FastString
fsLit "ALLOC_HEAP_ctr"))
1
]}
tickyAllocPrim :: CmmExpr
-> CmmExpr
-> CmmExpr -> FCode ()
tickyAllocPrim :: CmmExpr -> CmmExpr -> CmmExpr -> FCode ()
tickyAllocPrim _hdr :: CmmExpr
_hdr _goods :: CmmExpr
_goods _slop :: CmmExpr
_slop = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do
FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "ALLOC_PRIM_ctr")
FastString -> CmmExpr -> FCode ()
bumpTickyCounterByE (String -> FastString
fsLit "ALLOC_PRIM_adm") CmmExpr
_hdr
FastString -> CmmExpr -> FCode ()
bumpTickyCounterByE (String -> FastString
fsLit "ALLOC_PRIM_gds") CmmExpr
_goods
FastString -> CmmExpr -> FCode ()
bumpTickyCounterByE (String -> FastString
fsLit "ALLOC_PRIM_slp") CmmExpr
_slop
tickyAllocThunk :: CmmExpr -> CmmExpr -> FCode ()
tickyAllocThunk :: CmmExpr -> CmmExpr -> FCode ()
tickyAllocThunk _goods :: CmmExpr
_goods _slop :: CmmExpr
_slop = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do
FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "ALLOC_UP_THK_ctr")
FastString -> CmmExpr -> FCode ()
bumpTickyCounterByE (String -> FastString
fsLit "ALLOC_THK_gds") CmmExpr
_goods
FastString -> CmmExpr -> FCode ()
bumpTickyCounterByE (String -> FastString
fsLit "ALLOC_THK_slp") CmmExpr
_slop
tickyAllocPAP :: CmmExpr -> CmmExpr -> FCode ()
tickyAllocPAP :: CmmExpr -> CmmExpr -> FCode ()
tickyAllocPAP _goods :: CmmExpr
_goods _slop :: CmmExpr
_slop = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ do
FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "ALLOC_PAP_ctr")
FastString -> CmmExpr -> FCode ()
bumpTickyCounterByE (String -> FastString
fsLit "ALLOC_PAP_gds") CmmExpr
_goods
FastString -> CmmExpr -> FCode ()
bumpTickyCounterByE (String -> FastString
fsLit "ALLOC_PAP_slp") CmmExpr
_slop
tickyHeapCheck :: FCode ()
tickyHeapCheck :: FCode ()
tickyHeapCheck = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "HEAP_CHK_ctr")
tickyStackCheck :: FCode ()
tickyStackCheck :: FCode ()
tickyStackCheck = FCode () -> FCode ()
ifTicky (FCode () -> FCode ()) -> FCode () -> FCode ()
forall a b. (a -> b) -> a -> b
$ FastString -> FCode ()
bumpTickyCounter (String -> FastString
fsLit "STK_CHK_ctr")
ifTicky :: FCode () -> FCode ()
ifTicky :: FCode () -> FCode ()
ifTicky code :: FCode ()
code =
FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags FCode DynFlags -> (DynFlags -> FCode ()) -> FCode ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \dflags :: DynFlags
dflags -> Bool -> FCode () -> FCode ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Ticky DynFlags
dflags) FCode ()
code
tickyAllocdIsOn :: FCode Bool
tickyAllocdIsOn :: FCode Bool
tickyAllocdIsOn = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Ticky_Allocd (DynFlags -> Bool) -> FCode DynFlags -> FCode Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
tickyLNEIsOn :: FCode Bool
tickyLNEIsOn :: FCode Bool
tickyLNEIsOn = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Ticky_LNE (DynFlags -> Bool) -> FCode DynFlags -> FCode Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
tickyDynThunkIsOn :: FCode Bool
tickyDynThunkIsOn :: FCode Bool
tickyDynThunkIsOn = GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
Opt_Ticky_Dyn_Thunk (DynFlags -> Bool) -> FCode DynFlags -> FCode Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
ifTickyAllocd :: FCode () -> FCode ()
ifTickyAllocd :: FCode () -> FCode ()
ifTickyAllocd code :: FCode ()
code = FCode Bool
tickyAllocdIsOn FCode Bool -> (Bool -> FCode ()) -> FCode ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \b :: Bool
b -> Bool -> FCode () -> FCode ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
b FCode ()
code
ifTickyLNE :: FCode () -> FCode ()
ifTickyLNE :: FCode () -> FCode ()
ifTickyLNE code :: FCode ()
code = FCode Bool
tickyLNEIsOn FCode Bool -> (Bool -> FCode ()) -> FCode ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \b :: Bool
b -> Bool -> FCode () -> FCode ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
b FCode ()
code
ifTickyDynThunk :: FCode () -> FCode ()
ifTickyDynThunk :: FCode () -> FCode ()
ifTickyDynThunk code :: FCode ()
code = FCode Bool
tickyDynThunkIsOn FCode Bool -> (Bool -> FCode ()) -> FCode ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \b :: Bool
b -> Bool -> FCode () -> FCode ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
b FCode ()
code
bumpTickyCounter :: FastString -> FCode ()
bumpTickyCounter :: FastString -> FCode ()
bumpTickyCounter lbl :: FastString
lbl = CLabel -> FCode ()
bumpTickyLbl (UnitId -> FastString -> CLabel
mkCmmDataLabel UnitId
rtsUnitId FastString
lbl)
bumpTickyCounterBy :: FastString -> Int -> FCode ()
bumpTickyCounterBy :: FastString -> Int -> FCode ()
bumpTickyCounterBy lbl :: FastString
lbl = CLabel -> Int -> FCode ()
bumpTickyLblBy (UnitId -> FastString -> CLabel
mkCmmDataLabel UnitId
rtsUnitId FastString
lbl)
bumpTickyCounterByE :: FastString -> CmmExpr -> FCode ()
bumpTickyCounterByE :: FastString -> CmmExpr -> FCode ()
bumpTickyCounterByE lbl :: FastString
lbl = CLabel -> CmmExpr -> FCode ()
bumpTickyLblByE (UnitId -> FastString -> CLabel
mkCmmDataLabel UnitId
rtsUnitId FastString
lbl)
bumpTickyEntryCount :: CLabel -> FCode ()
bumpTickyEntryCount :: CLabel -> FCode ()
bumpTickyEntryCount lbl :: CLabel
lbl = do
DynFlags
dflags <- FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
CmmLit -> FCode ()
bumpTickyLit (CLabel -> Int -> CmmLit
cmmLabelOffB CLabel
lbl (DynFlags -> Int
oFFSET_StgEntCounter_entry_count DynFlags
dflags))
bumpTickyAllocd :: CLabel -> Int -> FCode ()
bumpTickyAllocd :: CLabel -> Int -> FCode ()
bumpTickyAllocd lbl :: CLabel
lbl bytes :: Int
bytes = do
DynFlags
dflags <- FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
CmmLit -> Int -> FCode ()
bumpTickyLitBy (CLabel -> Int -> CmmLit
cmmLabelOffB CLabel
lbl (DynFlags -> Int
oFFSET_StgEntCounter_allocd DynFlags
dflags)) Int
bytes
bumpTickyLbl :: CLabel -> FCode ()
bumpTickyLbl :: CLabel -> FCode ()
bumpTickyLbl lhs :: CLabel
lhs = CmmLit -> Int -> FCode ()
bumpTickyLitBy (CLabel -> Int -> CmmLit
cmmLabelOffB CLabel
lhs 0) 1
bumpTickyLblBy :: CLabel -> Int -> FCode ()
bumpTickyLblBy :: CLabel -> Int -> FCode ()
bumpTickyLblBy lhs :: CLabel
lhs = CmmLit -> Int -> FCode ()
bumpTickyLitBy (CLabel -> Int -> CmmLit
cmmLabelOffB CLabel
lhs 0)
bumpTickyLblByE :: CLabel -> CmmExpr -> FCode ()
bumpTickyLblByE :: CLabel -> CmmExpr -> FCode ()
bumpTickyLblByE lhs :: CLabel
lhs = CmmLit -> CmmExpr -> FCode ()
bumpTickyLitByE (CLabel -> Int -> CmmLit
cmmLabelOffB CLabel
lhs 0)
bumpTickyLit :: CmmLit -> FCode ()
bumpTickyLit :: CmmLit -> FCode ()
bumpTickyLit lhs :: CmmLit
lhs = CmmLit -> Int -> FCode ()
bumpTickyLitBy CmmLit
lhs 1
bumpTickyLitBy :: CmmLit -> Int -> FCode ()
bumpTickyLitBy :: CmmLit -> Int -> FCode ()
bumpTickyLitBy lhs :: CmmLit
lhs n :: Int
n = do
DynFlags
dflags <- FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
CmmAGraph -> FCode ()
emit (CmmType -> CmmExpr -> Int -> CmmAGraph
addToMem (DynFlags -> CmmType
bWord DynFlags
dflags) (CmmLit -> CmmExpr
CmmLit CmmLit
lhs) Int
n)
bumpTickyLitByE :: CmmLit -> CmmExpr -> FCode ()
bumpTickyLitByE :: CmmLit -> CmmExpr -> FCode ()
bumpTickyLitByE lhs :: CmmLit
lhs e :: CmmExpr
e = do
DynFlags
dflags <- FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
CmmAGraph -> FCode ()
emit (CmmType -> CmmExpr -> CmmExpr -> CmmAGraph
addToMemE (DynFlags -> CmmType
bWord DynFlags
dflags) (CmmLit -> CmmExpr
CmmLit CmmLit
lhs) CmmExpr
e)
bumpHistogram :: FastString -> Int -> FCode ()
bumpHistogram :: FastString -> Int -> FCode ()
bumpHistogram lbl :: FastString
lbl n :: Int
n = do
DynFlags
dflags <- FCode DynFlags
forall (m :: * -> *). HasDynFlags m => m DynFlags
getDynFlags
let offset :: Int
offset = Int
n Int -> Int -> Int
forall a. Ord a => a -> a -> a
`min` (DynFlags -> Int
tICKY_BIN_COUNT DynFlags
dflags Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1)
CmmAGraph -> FCode ()
emit (CmmType -> CmmExpr -> Int -> CmmAGraph
addToMem (DynFlags -> CmmType
bWord DynFlags
dflags)
(DynFlags -> Width -> CmmExpr -> CmmExpr -> CmmExpr
cmmIndexExpr DynFlags
dflags
(DynFlags -> Width
wordWidth DynFlags
dflags)
(CmmLit -> CmmExpr
CmmLit (CLabel -> CmmLit
CmmLabel (UnitId -> FastString -> CLabel
mkCmmDataLabel UnitId
rtsUnitId FastString
lbl)))
(CmmLit -> CmmExpr
CmmLit (Integer -> Width -> CmmLit
CmmInt (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offset) (DynFlags -> Width
wordWidth DynFlags
dflags))))
1)
showTypeCategory :: Type -> Char
showTypeCategory :: Type -> Char
showTypeCategory ty :: Type
ty
| Type -> Bool
isDictTy Type
ty = '+'
| Bool
otherwise = case HasCallStack => Type -> Maybe (TyCon, [Type])
Type -> Maybe (TyCon, [Type])
tcSplitTyConApp_maybe Type
ty of
Nothing -> '.'
Just (tycon :: TyCon
tycon, _) ->
(if TyCon -> Bool
isUnliftedTyCon TyCon
tycon then Char -> Char
Data.Char.toLower else Char -> Char
forall a. a -> a
id) (Char -> Char) -> Char -> Char
forall a b. (a -> b) -> a -> b
$
let anyOf :: t Unique -> Bool
anyOf us :: t Unique
us = TyCon -> Unique
forall a. Uniquable a => a -> Unique
getUnique TyCon
tycon Unique -> t Unique -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t Unique
us in
case () of
_ | [Unique] -> Bool
forall (t :: * -> *). Foldable t => t Unique -> Bool
anyOf [Unique
funTyConKey] -> '>'
| [Unique] -> Bool
forall (t :: * -> *). Foldable t => t Unique -> Bool
anyOf [Unique
charPrimTyConKey, Unique
charTyConKey] -> 'C'
| [Unique] -> Bool
forall (t :: * -> *). Foldable t => t Unique -> Bool
anyOf [Unique
doublePrimTyConKey, Unique
doubleTyConKey] -> 'D'
| [Unique] -> Bool
forall (t :: * -> *). Foldable t => t Unique -> Bool
anyOf [Unique
floatPrimTyConKey, Unique
floatTyConKey] -> 'F'
| [Unique] -> Bool
forall (t :: * -> *). Foldable t => t Unique -> Bool
anyOf [Unique
intPrimTyConKey, Unique
int32PrimTyConKey, Unique
int64PrimTyConKey,
Unique
intTyConKey, Unique
int8TyConKey, Unique
int16TyConKey, Unique
int32TyConKey, Unique
int64TyConKey
] -> 'I'
| [Unique] -> Bool
forall (t :: * -> *). Foldable t => t Unique -> Bool
anyOf [Unique
wordPrimTyConKey, Unique
word32PrimTyConKey, Unique
word64PrimTyConKey, Unique
wordTyConKey,
Unique
word8TyConKey, Unique
word16TyConKey, Unique
word32TyConKey, Unique
word64TyConKey
] -> 'W'
| [Unique] -> Bool
forall (t :: * -> *). Foldable t => t Unique -> Bool
anyOf [Unique
listTyConKey] -> 'L'
| TyCon -> Bool
isTupleTyCon TyCon
tycon -> 'T'
| TyCon -> Bool
isPrimTyCon TyCon
tycon -> 'P'
| TyCon -> Bool
isEnumerationTyCon TyCon
tycon -> 'E'
| Maybe DataCon -> Bool
forall a. Maybe a -> Bool
isJust (TyCon -> Maybe DataCon
tyConSingleDataCon_maybe TyCon
tycon) -> 'S'
| Bool
otherwise -> 'M'