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