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