\begin{code}
module CostCentre (
CostCentre(..), CcName, IsCafCC(..),
CostCentreStack,
CollectedCCs,
noCCS, currentCCS, dontCareCCS,
noCCSAttached, isCurrentCCS,
maybeSingletonCCS,
mkUserCC, mkAutoCC, mkAllCafsCC,
mkSingletonCCS,
isCafCCS, isCafCC, isSccCountCC, sccAbleCC, ccFromThisModule,
pprCostCentreCore,
costCentreUserName, costCentreUserNameFS,
costCentreSrcSpan,
cmpCostCentre
) where
import Binary
import Var
import Name
import Module
import Unique
import Outputable
import FastTypes
import SrcLoc
import FastString
import Util
import Data.Data
data CostCentre
= NormalCC {
cc_key :: !Int,
cc_name :: CcName,
cc_mod :: Module,
cc_loc :: SrcSpan,
cc_is_caf :: IsCafCC
}
| AllCafsCC {
cc_mod :: Module,
cc_loc :: SrcSpan
}
deriving (Data, Typeable)
type CcName = FastString
data IsCafCC = NotCafCC | CafCC
deriving (Eq, Ord, Data, Typeable)
instance Eq CostCentre where
c1 == c2 = case c1 `cmpCostCentre` c2 of { EQ -> True; _ -> False }
instance Ord CostCentre where
compare = cmpCostCentre
cmpCostCentre :: CostCentre -> CostCentre -> Ordering
cmpCostCentre (AllCafsCC {cc_mod = m1}) (AllCafsCC {cc_mod = m2})
= m1 `compare` m2
cmpCostCentre NormalCC {cc_key = n1, cc_mod = m1}
NormalCC {cc_key = n2, cc_mod = m2}
= (m1 `compare` m2) `thenCmp` (n1 `compare` n2)
cmpCostCentre other_1 other_2
= let
!tag1 = tag_CC other_1
!tag2 = tag_CC other_2
in
if tag1 <# tag2 then LT else GT
where
tag_CC (NormalCC {}) = _ILIT(0)
tag_CC (AllCafsCC {}) = _ILIT(1)
isCafCC :: CostCentre -> Bool
isCafCC (AllCafsCC {}) = True
isCafCC (NormalCC {cc_is_caf = CafCC}) = True
isCafCC _ = False
isSccCountCC :: CostCentre -> Bool
isSccCountCC cc | isCafCC cc = False
| otherwise = True
sccAbleCC :: CostCentre -> Bool
sccAbleCC cc | isCafCC cc = False
| otherwise = True
ccFromThisModule :: CostCentre -> Module -> Bool
ccFromThisModule cc m = cc_mod cc == m
mkUserCC :: FastString -> Module -> SrcSpan -> Unique -> CostCentre
mkUserCC cc_name mod loc key
= NormalCC { cc_key = getKey key, cc_name = cc_name, cc_mod = mod, cc_loc = loc,
cc_is_caf = NotCafCC
}
mkAutoCC :: Id -> Module -> IsCafCC -> CostCentre
mkAutoCC id mod is_caf
= NormalCC { cc_key = getKey (getUnique id),
cc_name = str, cc_mod = mod,
cc_loc = nameSrcSpan (getName id),
cc_is_caf = is_caf
}
where
name = getName id
str | isExternalName name = occNameFS (getOccName id)
| otherwise = occNameFS (getOccName id)
`appendFS`
mkFastString ('_' : show (getUnique name))
mkAllCafsCC :: Module -> SrcSpan -> CostCentre
mkAllCafsCC m loc = AllCafsCC { cc_mod = m, cc_loc = loc }
data CostCentreStack
= NoCCS
| CurrentCCS
| DontCareCCS
| SingletonCCS CostCentre
deriving (Eq, Ord)
type CollectedCCs
= ( [CostCentre]
, [CostCentre]
, [CostCentreStack]
)
noCCS, currentCCS, dontCareCCS :: CostCentreStack
noCCS = NoCCS
currentCCS = CurrentCCS
dontCareCCS = DontCareCCS
noCCSAttached :: CostCentreStack -> Bool
noCCSAttached NoCCS = True
noCCSAttached _ = False
isCurrentCCS :: CostCentreStack -> Bool
isCurrentCCS CurrentCCS = True
isCurrentCCS _ = False
isCafCCS :: CostCentreStack -> Bool
isCafCCS (SingletonCCS cc) = isCafCC cc
isCafCCS _ = False
maybeSingletonCCS :: CostCentreStack -> Maybe CostCentre
maybeSingletonCCS (SingletonCCS cc) = Just cc
maybeSingletonCCS _ = Nothing
mkSingletonCCS :: CostCentre -> CostCentreStack
mkSingletonCCS cc = SingletonCCS cc
instance Outputable CostCentreStack where
ppr NoCCS = ptext (sLit "NO_CCS")
ppr CurrentCCS = ptext (sLit "CCCS")
ppr DontCareCCS = ptext (sLit "CCS_DONT_CARE")
ppr (SingletonCCS cc) = ppr cc <> ptext (sLit "_ccs")
instance Outputable CostCentre where
ppr cc = getPprStyle $ \ sty ->
if codeStyle sty
then ppCostCentreLbl cc
else text (costCentreUserName cc)
pprCostCentreCore :: CostCentre -> SDoc
pprCostCentreCore (AllCafsCC {cc_mod = m})
= text "__sccC" <+> braces (ppr m)
pprCostCentreCore (NormalCC {cc_key = key, cc_name = n, cc_mod = m, cc_loc = loc,
cc_is_caf = caf})
= text "__scc" <+> braces (hsep [
ppr m <> char '.' <> ftext n,
ifPprDebug (ppr key),
pp_caf caf,
ifPprDebug (ppr loc)
])
pp_caf :: IsCafCC -> SDoc
pp_caf CafCC = text "__C"
pp_caf _ = empty
ppCostCentreLbl :: CostCentre -> SDoc
ppCostCentreLbl (AllCafsCC {cc_mod = m}) = ppr m <> text "_CAFs_cc"
ppCostCentreLbl (NormalCC {cc_key = k, cc_name = n, cc_mod = m,
cc_is_caf = is_caf})
= ppr m <> char '_' <> ztext (zEncodeFS n) <> char '_' <>
case is_caf of { CafCC -> ptext (sLit "CAF"); _ -> ppr (mkUniqueGrimily k)} <> text "_cc"
costCentreUserName :: CostCentre -> String
costCentreUserName = unpackFS . costCentreUserNameFS
costCentreUserNameFS :: CostCentre -> FastString
costCentreUserNameFS (AllCafsCC {}) = mkFastString "CAF"
costCentreUserNameFS (NormalCC {cc_name = name, cc_is_caf = is_caf})
= case is_caf of
CafCC -> mkFastString "CAF:" `appendFS` name
_ -> name
costCentreSrcSpan :: CostCentre -> SrcSpan
costCentreSrcSpan = cc_loc
instance Binary IsCafCC where
put_ bh CafCC = do
putByte bh 0
put_ bh NotCafCC = do
putByte bh 1
get bh = do
h <- getByte bh
case h of
0 -> do return CafCC
_ -> do return NotCafCC
instance Binary CostCentre where
put_ bh (NormalCC aa ab ac _ad ae) = do
putByte bh 0
put_ bh aa
put_ bh ab
put_ bh ac
put_ bh ae
put_ bh (AllCafsCC ae _af) = do
putByte bh 1
put_ bh ae
get bh = do
h <- getByte bh
case h of
0 -> do aa <- get bh
ab <- get bh
ac <- get bh
ae <- get bh
return (NormalCC aa ab ac noSrcSpan ae)
_ -> do ae <- get bh
return (AllCafsCC ae noSrcSpan)
\end{code}