5efe37a8c8da19771964a670261e8198d7de52dc
[ghc-hetmet.git] / ghc / compiler / profiling / CostCentre.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[CostCentre]{The @CostCentre@ data type}
5
6 \begin{code}
7 module CostCentre (
8         CostCentre(..), CcName, IsDupdCC(..), IsCafCC(..),
9                 -- All abstract except to friend: ParseIface.y
10
11         CostCentreStack,
12         CollectedCCs,
13         noCCS, subsumedCCS, currentCCS, overheadCCS, dontCareCCS,
14         noCostCentre, noCCAttached,
15         noCCSAttached, isCurrentCCS,  isSubsumedCCS, currentOrSubsumedCCS,
16         isDerivedFromCurrentCCS,
17
18         mkUserCC, mkAutoCC, mkAllCafsCC, 
19         mkSingletonCCS, dupifyCC, pushCCOnCCS,
20         isCafCCS,
21         isSccCountCostCentre,
22         sccAbleCostCentre,
23         ccFromThisModule,
24
25         pprCostCentreDecl, pprCostCentreStackDecl, pprCostCentreCore,
26
27         cmpCostCentre   -- used for removing dups in a list
28     ) where
29
30 #include "HsVersions.h"
31
32 import Var              ( Id )
33 import Name             ( UserFS, EncodedFS, encodeFS, decode,
34                           getOccName, occNameFS
35                         )
36 import Module           ( Module, ModuleName, moduleName,
37                           moduleNameUserString
38                         )
39 import Outputable       
40 import CStrings         ( pprStringInCStyle )
41 import FastTypes
42 import FastString
43 import Util             ( thenCmp )
44 \end{code}
45
46 A Cost Centre Stack is something that can be attached to a closure.
47 This is either:
48         
49         - the current cost centre stack (CCCS)
50         - a pre-defined cost centre stack (there are several
51           pre-defined CCSs, see below).
52
53 \begin{code}
54 data CostCentreStack
55   = NoCCS
56
57   | CurrentCCS          -- Pinned on a let(rec)-bound 
58                         -- thunk/function/constructor, this says that the 
59                         -- cost centre to be attached to the object, when it 
60                         -- is allocated, is whatever is in the 
61                         -- current-cost-centre-stack register.
62
63   | SubsumedCCS         -- Cost centre stack for top-level subsumed functions
64                         -- (CAFs get an AllCafsCC).
65                         -- Its execution costs get subsumed into the caller.
66                         -- This guy is *only* ever pinned on static closures,
67                         -- and is *never* the cost centre for an SCC construct.
68
69   | OverheadCCS         -- We charge costs due to the profiling-system
70                         -- doing its work to "overhead".
71                         --
72                         -- Objects whose CCS is "Overhead"
73                         -- have their *allocation* charged to "overhead",
74                         -- but have the current CCS put into the object
75                         -- itself.
76
77                         -- For example, if we transform "f g" to "let
78                         -- g' = g in f g'" (so that something about
79                         -- profiling works better...), then we charge
80                         -- the *allocation* of g' to OverheadCCS, but
81                         -- we put the cost-centre of the call to f
82                         -- (i.e., current CCS) into the g' object.  When
83                         -- g' is entered, the CCS of the call
84                         -- to f will be set.
85
86   | DontCareCCS         -- We need a CCS to stick in static closures
87                         -- (for data), but we *don't* expect them to
88                         -- accumulate any costs.  But we still need
89                         -- the placeholder.  This CCS is it.
90
91   | PushCC CostCentre CostCentreStack
92                 -- These are used during code generation as the CCSs
93                 -- attached to closures.  A PushCC never appears as
94                 -- the argument to an _scc_.
95                 --
96                 -- The tail (2nd argument) is either NoCCS, indicating
97                 -- a staticly allocated CCS, or CurrentCCS indicating
98                 -- a dynamically created CCS.  We only support
99                 -- statically allocated *singleton* CCSs at the
100                 -- moment, for the purposes of initialising the CCS
101                 -- field of a CAF.
102
103   deriving (Eq, Ord)    -- needed for Ord on CLabel
104 \end{code}
105
106 A Cost Centre is the argument of an _scc_ expression.
107  
108 \begin{code}
109 data CostCentre
110   = NoCostCentre        -- Having this constructor avoids having
111                         -- to use "Maybe CostCentre" all the time.
112
113   | NormalCC {  
114                 cc_name :: CcName,      -- Name of the cost centre itself
115                 cc_mod  :: ModuleName,  -- Name of module defining this CC.
116                 cc_is_dupd :: IsDupdCC, -- see below
117                 cc_is_caf  :: IsCafCC   -- see below
118     }
119
120   | AllCafsCC { 
121                 cc_mod  :: ModuleName   -- Name of module defining this CC.
122     }
123
124 type CcName = EncodedFS
125
126 data IsDupdCC
127   = OriginalCC  -- This says how the CC is *used*.  Saying that
128   | DupdCC              -- it is DupdCC doesn't make it a different
129                         -- CC, just that it a sub-expression which has
130                         -- been moved ("dupd") into a different scope.
131                         --
132                         -- The point about a dupd SCC is that we don't
133                         -- count entries to it, because it's not the
134                         -- "original" one.
135                         --
136                         -- In the papers, it's called "SCCsub",
137                         --  i.e. SCCsub CC == SCC DupdCC,
138                         -- but we are trying to avoid confusion between
139                         -- "subd" and "subsumed".  So we call the former
140                         -- "dupd".
141
142 data IsCafCC = CafCC | NotCafCC
143
144 -- synonym for triple which describes the cost centre info in the generated
145 -- code for a module.
146 type CollectedCCs
147   = ( [CostCentre]       -- local cost-centres that need to be decl'd
148     , [CostCentre]       -- "extern" cost-centres
149     , [CostCentreStack]  -- pre-defined "singleton" cost centre stacks
150     )
151 \end{code}
152
153 WILL: Would there be any merit to recording ``I am now using a
154 cost-centre from another module''?  I don't know if this would help a
155 user; it might be interesting to us to know how much computation is
156 being moved across module boundaries.
157
158 SIMON: Maybe later...
159
160 \begin{code}
161
162 noCCS                   = NoCCS
163 subsumedCCS             = SubsumedCCS
164 currentCCS              = CurrentCCS
165 overheadCCS             = OverheadCCS
166 dontCareCCS             = DontCareCCS
167
168 noCostCentre            = NoCostCentre
169 \end{code}
170
171 Predicates on Cost-Centre Stacks
172
173 \begin{code}
174 noCCSAttached NoCCS                     = True
175 noCCSAttached _                         = False
176
177 noCCAttached NoCostCentre               = True
178 noCCAttached _                          = False
179
180 isCurrentCCS CurrentCCS                 = True
181 isCurrentCCS _                          = False
182
183 isSubsumedCCS SubsumedCCS               = True
184 isSubsumedCCS _                         = False
185
186 isCafCCS (PushCC cc NoCCS)              = isCafCC cc
187 isCafCCS _                              = False
188
189 isDerivedFromCurrentCCS CurrentCCS      = True
190 isDerivedFromCurrentCCS (PushCC _ ccs)  = isDerivedFromCurrentCCS ccs
191 isDerivedFromCurrentCCS _               = False
192
193 currentOrSubsumedCCS SubsumedCCS        = True
194 currentOrSubsumedCCS CurrentCCS         = True
195 currentOrSubsumedCCS _                  = False
196 \end{code}
197
198 Building cost centres
199
200 \begin{code}
201 mkUserCC :: UserFS -> Module -> CostCentre
202 mkUserCC cc_name mod
203   = NormalCC { cc_name = encodeFS cc_name, cc_mod =  moduleName mod,
204                cc_is_dupd = OriginalCC, cc_is_caf = NotCafCC {-might be changed-}
205     }
206
207 mkAutoCC :: Id -> Module -> IsCafCC -> CostCentre
208 mkAutoCC id mod is_caf
209   = NormalCC { cc_name = occNameFS (getOccName id), cc_mod =  moduleName mod,
210                cc_is_dupd = OriginalCC, cc_is_caf = is_caf
211     }
212
213 mkAllCafsCC m = AllCafsCC  { cc_mod = moduleName m }
214
215
216
217 mkSingletonCCS :: CostCentre -> CostCentreStack
218 mkSingletonCCS cc = pushCCOnCCS cc NoCCS
219
220 pushCCOnCCS :: CostCentre -> CostCentreStack -> CostCentreStack
221 pushCCOnCCS = PushCC
222
223 dupifyCC cc = cc {cc_is_dupd = DupdCC}
224
225 isEmptyCC, isCafCC, isDupdCC :: CostCentre -> Bool
226
227 isEmptyCC (NoCostCentre)                = True
228 isEmptyCC _                             = False
229
230 isCafCC (AllCafsCC {})                   = True
231 isCafCC (NormalCC {cc_is_caf = CafCC}) = True
232 isCafCC _                                = False
233
234 isDupdCC (NormalCC   {cc_is_dupd = DupdCC}) = True
235 isDupdCC _                                   = False
236
237 isSccCountCostCentre :: CostCentre -> Bool
238   -- Is this a cost-centre which records scc counts
239
240 #if DEBUG
241 isSccCountCostCentre NoCostCentre  = panic "isSccCount:NoCostCentre"
242 #endif
243 isSccCountCostCentre cc | isCafCC cc  = False
244                         | isDupdCC cc = False
245                         | otherwise   = True
246
247 sccAbleCostCentre :: CostCentre -> Bool
248   -- Is this a cost-centre which can be sccd ?
249
250 #if DEBUG
251 sccAbleCostCentre NoCostCentre  = panic "sccAbleCC:NoCostCentre"
252 #endif
253 sccAbleCostCentre cc | isCafCC cc = False
254                      | otherwise  = True
255
256 ccFromThisModule :: CostCentre -> Module -> Bool
257 ccFromThisModule cc m = cc_mod cc == moduleName m
258 \end{code}
259
260 \begin{code}
261 instance Eq CostCentre where
262         c1 == c2 = case c1 `cmpCostCentre` c2 of { EQ -> True; _ -> False }
263
264 instance Ord CostCentre where
265         compare = cmpCostCentre
266
267 cmpCostCentre :: CostCentre -> CostCentre -> Ordering
268
269 cmpCostCentre (AllCafsCC  {cc_mod = m1}) (AllCafsCC  {cc_mod = m2}) = m1 `compare` m2
270
271 cmpCostCentre (NormalCC {cc_name = n1, cc_mod =  m1, cc_is_caf = c1}) 
272               (NormalCC {cc_name = n2, cc_mod =  m2, cc_is_caf = c2}) 
273     -- first key is module name, then we use "kinds" (which include
274     -- names) and finally the caf flag
275   = (m1 `compare` m2) `thenCmp` (n1 `compare` n2) `thenCmp` (c1 `cmp_caf` c2)
276
277 cmpCostCentre other_1 other_2
278   = let
279         tag1 = tag_CC other_1
280         tag2 = tag_CC other_2
281     in
282     if tag1 <# tag2 then LT else GT
283   where
284     tag_CC (NormalCC   {}) = (_ILIT 1 :: FastInt)
285     tag_CC (AllCafsCC  {}) = _ILIT 2
286
287 cmp_caf NotCafCC CafCC     = LT
288 cmp_caf NotCafCC NotCafCC  = EQ
289 cmp_caf CafCC    CafCC     = EQ
290 cmp_caf CafCC    NotCafCC  = GT
291 \end{code}
292
293 -----------------------------------------------------------------------------
294 Printing Cost Centre Stacks.
295
296 The outputable instance for CostCentreStack prints the CCS as a C
297 expression.
298
299 NOTE: Not all cost centres are suitable for using in a static
300 initializer.  In particular, the PushCC forms where the tail is CCCS
301 may only be used in inline C code because they expand to a
302 non-constant C expression.
303
304 \begin{code}
305 instance Outputable CostCentreStack where
306   ppr NoCCS             = ptext SLIT("NO_CCS")
307   ppr CurrentCCS        = ptext SLIT("CCCS")
308   ppr OverheadCCS       = ptext SLIT("CCS_OVERHEAD")
309   ppr DontCareCCS       = ptext SLIT("CCS_DONT_CARE")
310   ppr SubsumedCCS       = ptext SLIT("CCS_SUBSUMED")
311   ppr (PushCC cc NoCCS) = ppr cc <> ptext SLIT("_ccs")
312   ppr (PushCC cc ccs)   = ptext SLIT("PushCostCentre") <> 
313                            parens (ppr ccs <> comma <> ppr cc)
314
315 -- print the static declaration for a singleton CCS.
316 pprCostCentreStackDecl :: CostCentreStack -> SDoc
317 pprCostCentreStackDecl ccs@(PushCC cc NoCCS)
318   = hcat [ ptext SLIT("CCS_DECLARE"), char '(',
319            ppr ccs,             comma,  -- better be codeStyle
320            ppCostCentreLbl cc,  comma,
321            empty,       -- Now always externally visible
322            text ");"
323          ]
324
325 pprCostCentreStackDecl ccs 
326   = pprPanic "pprCostCentreStackDecl: " (ppr ccs)
327 \end{code}
328
329 -----------------------------------------------------------------------------
330 Printing Cost Centres.
331
332 There are several different ways in which we might want to print a
333 cost centre:
334
335         - the name of the cost centre, for profiling output (a C string)
336         - the label, i.e. C label for cost centre in .hc file.
337         - the debugging name, for output in -ddump things
338         - the interface name, for printing in _scc_ exprs in iface files.
339
340 The last 3 are derived from costCentreStr below.  The first is given
341 by costCentreName.
342
343 \begin{code}
344 instance Outputable CostCentre where
345   ppr cc = getPprStyle $ \ sty ->
346            if codeStyle sty
347            then ppCostCentreLbl cc
348            else text (costCentreUserName cc)
349
350 -- Printing in an interface file or in Core generally
351 pprCostCentreCore (AllCafsCC {cc_mod = m})
352   = text "__sccC" <+> braces (ppr m)
353 pprCostCentreCore (NormalCC {cc_name = n, cc_mod = m,
354                              cc_is_caf = caf, cc_is_dupd = dup})
355   = text "__scc" <+> braces (hsep [
356         ftext n,
357         ppr m,  
358         pp_dup dup,
359         pp_caf caf
360     ])
361
362 pp_dup DupdCC = char '!'
363 pp_dup other   = empty
364
365 pp_caf CafCC = text "__C"
366 pp_caf other   = empty
367
368
369 -- Printing as a C label
370 ppCostCentreLbl (NoCostCentre)            = text "NONE_cc"
371 ppCostCentreLbl (AllCafsCC  {cc_mod = m}) = ppr m <> text "_CAFs_cc"
372 ppCostCentreLbl (NormalCC {cc_name = n, cc_mod = m, cc_is_caf = is_caf}) 
373   = ppr m <> ftext n <> 
374         text (case is_caf of { CafCC -> "_CAF"; _ -> "" }) <> text "_cc"
375
376 -- This is the name to go in the user-displayed string, 
377 -- recorded in the cost centre declaration
378 costCentreUserName (NoCostCentre)  = "NO_CC"
379 costCentreUserName (AllCafsCC {})  = "CAF"
380 costCentreUserName cc@(NormalCC {cc_name = name, cc_is_caf = is_caf})
381   =  case is_caf of { CafCC -> "CAF:";   _ -> "" } ++ decode (unpackFS name)
382 \end{code}
383
384 Cost Centre Declarations
385
386 \begin{code}
387 #ifdef DEBUG
388 pprCostCentreDecl is_local (NoCostCentre)
389   = panic "pprCostCentreDecl: no cost centre!"
390 #endif
391 pprCostCentreDecl is_local cc
392   = if is_local then
393         hcat [
394             ptext SLIT("CC_DECLARE"),char '(',
395             cc_ident,                                                   comma,
396             pprStringInCStyle (costCentreUserName cc),                  comma,
397             pprStringInCStyle (moduleNameUserString mod_name),          comma,
398             is_subsumed,                                                comma,
399             empty,      -- Now always externally visible
400             text ");"]
401     else
402         hcat [ ptext SLIT("CC_EXTERN"),char '(', cc_ident, text ");" ]
403   where
404     cc_ident    = ppCostCentreLbl cc
405     mod_name    = cc_mod cc
406     is_subsumed = ccSubsumed cc
407
408 ccSubsumed :: CostCentre -> SDoc                -- subsumed value
409 ccSubsumed cc | isCafCC  cc = ptext SLIT("CC_IS_CAF")
410               | otherwise   = ptext SLIT("CC_IS_BORING")
411 \end{code}