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