[project @ 1998-01-08 18:03:08 by simonm]
[ghc-hetmet.git] / ghc / compiler / profiling / CostCentre.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[CostCentre]{The @CostCentre@ data type}
5
6 \begin{code}
7 module CostCentre (
8         CostCentre, CcKind, IsDupdCC{-ToDo:rm-}, IsCafCC(..),
9         noCostCentre, subsumedCosts,
10         useCurrentCostCentre,
11         noCostCentreAttached, costsAreSubsumed, isCurrentCostCentre,
12         currentOrSubsumedCosts,
13         preludeCafsCostCentre, preludeDictsCostCentre,
14         overheadCostCentre, dontCareCostCentre,
15
16         mkUserCC, mkAutoCC, mkDictCC, mkAllCafsCC, mkAllDictsCC,
17         cafifyCC, dupifyCC,
18         isCafCC, isDictCC, isDupdCC,
19         isSccCountCostCentre,
20         sccAbleCostCentre,
21         ccFromThisModule,
22         ccMentionsId,
23
24         uppCostCentre, uppCostCentreDecl, showCostCentre, -- printing
25
26         cmpCostCentre   -- used for removing dups in a list
27     ) where
28
29 #include "HsVersions.h"
30
31 import Id               ( externallyVisibleId, GenId, showId, Id )
32 import CStrings         ( identToC, stringToC )
33 import Name             ( OccName, getOccString, moduleString, nameString )
34 import Outputable       
35 import Util             ( panic, panic#, assertPanic, thenCmp )
36
37 pprIdInUnfolding = panic "Whoops"
38 \end{code}
39
40 \begin{code}
41 data CostCentre
42   = NoCostCentre        -- Having this constructor avoids having
43                         -- to use "Maybe CostCentre" all the time.
44
45   | NormalCC    CcKind   -- CcKind will include a cost-centre name
46                 FAST_STRING      -- Name of module defining this CC.
47                 FAST_STRING   -- "Group" that this CC is in.
48                 IsDupdCC -- see below
49                 IsCafCC  -- see below
50
51   | CurrentCC           -- Pinned on a let(rec)-bound thunk/function/constructor,
52                         -- this says that the cost centre to be attached to
53                         -- the object, when it is allocated, is whatever is in the
54                         -- current-cost-centre register.
55                         -- This guy is *never* the cost centre for an SCC construct,
56                         -- and is only used for *local* (non-top-level) definitions.
57
58   | SubsumedCosts       -- Cost centre 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   | AllCafsCC   FAST_STRING     -- Ditto for CAFs.
65                 FAST_STRING  -- We record module and group names.
66                         -- Again, one "big" CAF cc per module, where all
67                         -- CAF costs are attributed unless the user asked for
68                         -- per-individual-CAF cost attribution.
69
70   | AllDictsCC  FAST_STRING     -- Ditto for dictionaries.
71                 FAST_STRING  -- We record module and group names.
72                         -- Again, one "big" DICT cc per module, where all
73                         -- DICT costs are attributed unless the user asked for
74                         -- per-individual-DICT cost attribution.
75                 IsDupdCC -- see below
76
77   | OverheadCC          -- We charge costs due to the profiling-system
78                         -- doing its work to "overhead".
79                         --
80                         -- Objects whose cost-centre is "Overhead"
81                         -- have their *allocation* charged to "overhead",
82                         -- but have the current CC put into the object
83                         -- itself.
84                         --
85                         -- For example, if we transform "f g" to "let
86                         -- g' = g in f g'" (so that something about
87                         -- profiling works better...), then we charge
88                         -- the *allocation* of g' to OverheadCC, but
89                         -- we put the cost-centre of the call to f
90                         -- (i.e., current CC) into the g' object.  When
91                         -- g' is entered, the cost-centre of the call
92                         -- to f will be set.
93
94   | PreludeCafsCC       -- In compiling the prelude, we do sometimes
95   | PreludeDictsCC      -- need a CC to blame; i.e., when there's a CAF,
96                         -- or other costs that really shouldn't be
97                         -- subsumed/blamed-on-the-caller.  These costs
98                         -- should be *small*.  We treat PreludeCafsCC
99                         -- as if it were shorthand for
100                         -- (AllCafsCC <PreludeSomething> _).  Analogously
101                         -- for PreludeDictsCC...
102         IsDupdCC        -- see below/above
103
104   | DontCareCC          -- We need a cost-centre to stick in static closures
105                         -- (for data), but we *don't* expect them to
106                         -- accumulate any costs.  But we still need
107                         -- the placeholder.  This CC is it.
108
109 data CcKind
110   = UserCC  FAST_STRING -- Supplied by user: String is the cc name
111   | AutoCC  Id          -- CC -auto-magically inserted for that Id
112   | DictCC  Id
113
114 data IsDupdCC
115   = AnOriginalCC        -- This says how the CC is *used*.  Saying that
116   | ADupdCC             -- it is ADupdCC doesn't make it a different
117                         -- CC, just that it a sub-expression which has
118                         -- been moved ("dupd") into a different scope.
119                         -- In the papers, it's called "SCCsub",
120                         --  i.e. SCCsub CC == SCC ADupdCC,
121                         -- but we are trying to avoid confusion between
122                         -- "subd" and "subsumed".  So we call the former
123                         -- "dupd".
124
125 data IsCafCC
126   = IsCafCC
127   | IsNotCafCC
128 \end{code}
129
130 WILL: Would there be any merit to recording ``I am now using a
131 cost-centre from another module''?  I don't know if this would help a
132 user; it might be interesting to us to know how much computation is
133 being moved across module boundaries.
134
135 SIMON: Maybe later...
136
137 \begin{code}
138 noCostCentre  = NoCostCentre
139 subsumedCosts = SubsumedCosts
140 useCurrentCostCentre = CurrentCC
141 overheadCostCentre = OverheadCC
142 preludeCafsCostCentre = PreludeCafsCC
143 dontCareCostCentre = DontCareCC
144 preludeDictsCostCentre is_dupd
145   = PreludeDictsCC (if is_dupd then ADupdCC else AnOriginalCC)
146
147 noCostCentreAttached NoCostCentre  = True
148 noCostCentreAttached _             = False
149
150 isCurrentCostCentre CurrentCC = True
151 isCurrentCostCentre _         = False
152
153 costsAreSubsumed SubsumedCosts  = True
154 costsAreSubsumed _              = False
155
156 currentOrSubsumedCosts SubsumedCosts    = True
157 currentOrSubsumedCosts CurrentCC        = True
158 currentOrSubsumedCosts _                = False
159
160 mkUserCC :: FAST_STRING -> FAST_STRING -> FAST_STRING -> CostCentre
161
162 mkUserCC cc_name module_name group_name
163   = NormalCC (UserCC cc_name) module_name group_name
164              AnOriginalCC IsNotCafCC{-might be changed-}
165
166 mkDictCC, mkAutoCC :: Id -> FAST_STRING -> FAST_STRING -> IsCafCC -> CostCentre
167
168 mkDictCC id module_name group_name is_caf
169   = NormalCC (DictCC id) module_name group_name
170              AnOriginalCC is_caf
171
172 mkAutoCC id module_name group_name is_caf
173   = NormalCC (AutoCC id) module_name group_name
174              AnOriginalCC is_caf
175
176 mkAllCafsCC  m g   = AllCafsCC  m g
177 mkAllDictsCC m g is_dupd
178   = AllDictsCC m g (if is_dupd then ADupdCC else AnOriginalCC)
179
180 cafifyCC, dupifyCC  :: CostCentre -> CostCentre
181
182 cafifyCC cc@(AllDictsCC _ _ _) = cc -- ToDo ???
183 cafifyCC cc@(PreludeDictsCC _) = cc --    ditto
184 cafifyCC (NormalCC kind m g is_dupd is_caf)
185   = ASSERT(not_a_calf_already is_caf)
186     NormalCC kind m g is_dupd IsCafCC
187   where
188     not_a_calf_already IsCafCC = False
189     not_a_calf_already _       = True
190 cafifyCC cc = panic ("cafifyCC"++(showCostCentre False cc))
191
192 dupifyCC (AllDictsCC m g _) = AllDictsCC m g ADupdCC
193 dupifyCC (PreludeDictsCC _) = PreludeDictsCC ADupdCC
194 dupifyCC (NormalCC kind m g is_dupd is_caf)
195   = NormalCC kind m g ADupdCC is_caf
196 dupifyCC cc = panic ("dupifyCC"++(showCostCentre False cc))
197
198 isCafCC, isDictCC, isDupdCC :: CostCentre -> Bool
199
200 isCafCC (AllCafsCC _ _)            = True
201 isCafCC PreludeCafsCC              = True
202 isCafCC (NormalCC _ _ _ _ IsCafCC) = True
203 isCafCC _                          = False
204
205 isDictCC (AllDictsCC _ _ _)             = True
206 isDictCC (PreludeDictsCC _)             = True
207 isDictCC (NormalCC (DictCC _) _ _ _ _)  = True
208 isDictCC _                              = False
209
210 isDupdCC (AllDictsCC _ _ ADupdCC)   = True
211 isDupdCC (PreludeDictsCC ADupdCC)   = True
212 isDupdCC (NormalCC _ _ _ ADupdCC _) = True
213 isDupdCC _                          = False
214
215 isSccCountCostCentre :: CostCentre -> Bool
216   -- Is this a cost-centre which records scc counts
217
218 #if DEBUG
219 isSccCountCostCentre NoCostCentre  = panic "isSccCount:NoCostCentre"
220 isSccCountCostCentre SubsumedCosts = panic "isSccCount:SubsumedCosts"
221 isSccCountCostCentre CurrentCC     = panic "isSccCount:CurrentCC"
222 isSccCountCostCentre DontCareCC    = panic "isSccCount:DontCareCC"
223 #endif
224 isSccCountCostCentre OverheadCC       = False
225 isSccCountCostCentre cc | isCafCC cc  = False
226                         | isDupdCC cc = False
227                         | isDictCC cc = True
228                         | otherwise   = True
229
230 sccAbleCostCentre :: CostCentre -> Bool
231   -- Is this a cost-centre which can be sccd ?
232
233 #if DEBUG
234 sccAbleCostCentre NoCostCentre  = panic "sccAbleCC:NoCostCentre"
235 sccAbleCostCentre SubsumedCosts = panic "sccAbleCC:SubsumedCosts"
236 sccAbleCostCentre CurrentCC     = panic "sccAbleCC:CurrentCC"
237 sccAbleCostCentre DontCareCC    = panic "sccAbleCC:DontCareCC"
238 #endif
239 sccAbleCostCentre OverheadCC      = False
240 sccAbleCostCentre cc | isCafCC cc = False
241                      | otherwise  = True
242
243 ccFromThisModule :: CostCentre -> FAST_STRING{-module name-} -> Bool
244
245 ccFromThisModule (NormalCC _ m _ _ _) mod_name = m == mod_name
246 ccFromThisModule (AllCafsCC  m _)     mod_name = m == mod_name
247 ccFromThisModule (AllDictsCC m _ _)   mod_name = m == mod_name
248 ccFromThisModule PreludeCafsCC        _        = False
249 ccFromThisModule (PreludeDictsCC _)   _        = False
250 ccFromThisModule OverheadCC           _        = False
251 ccFromThisModule DontCareCC           _        = False
252   -- shouldn't ask about any others!
253 \end{code}
254
255 \begin{code}
256 ccMentionsId :: CostCentre -> Maybe Id
257
258 ccMentionsId (NormalCC (AutoCC id) _ _ _ _) = Just id
259 ccMentionsId (NormalCC (DictCC id) _ _ _ _) = Just id
260 ccMentionsId other                          = Nothing
261 \end{code}
262
263 \begin{code}
264 cmpCostCentre :: CostCentre -> CostCentre -> Ordering
265
266 cmpCostCentre (AllCafsCC  m1 _)   (AllCafsCC  m2 _)   = m1 `compare` m2
267 cmpCostCentre (AllDictsCC m1 _ _) (AllDictsCC m2 _ _) = m1 `compare` m2
268 cmpCostCentre PreludeCafsCC       PreludeCafsCC       = EQ
269 cmpCostCentre (PreludeDictsCC _)  (PreludeDictsCC _)  = EQ
270 cmpCostCentre OverheadCC          OverheadCC          = EQ
271 cmpCostCentre DontCareCC          DontCareCC          = EQ
272
273 cmpCostCentre (NormalCC k1 m1 _ _ c1) (NormalCC k2 m2 _ _ c2)
274     -- first key is module name, then we use "kinds" (which include
275     -- names) and finally the caf flag
276   = (m1 `compare` m2) `thenCmp` (k1 `cmp_kind` k2) `thenCmp` (c1 `cmp_caf` c2)
277
278 cmpCostCentre other_1 other_2
279   = let
280         tag1 = tag_CC other_1
281         tag2 = tag_CC other_2
282     in
283     if tag1 _LT_ tag2 then LT else GT
284   where
285     tag_CC (NormalCC _ _ _ _ _) = (ILIT(1) :: FAST_INT)
286     tag_CC (AllCafsCC  _ _)     = ILIT(2)
287     tag_CC (AllDictsCC _ _ _)   = ILIT(3)
288     tag_CC PreludeCafsCC        = ILIT(4)
289     tag_CC (PreludeDictsCC _)   = ILIT(5)
290     tag_CC OverheadCC           = ILIT(6)
291     tag_CC DontCareCC           = ILIT(7)
292
293     -- some BUG avoidance here...
294     tag_CC NoCostCentre  = panic# "tag_CC:NoCostCentre"
295     tag_CC SubsumedCosts = panic# "tag_CC:SubsumedCosts"
296     tag_CC CurrentCC     = panic# "tag_CC:SubsumedCosts"
297
298
299 cmp_kind (UserCC n1) (UserCC n2) = n1 `compare` n2
300 cmp_kind (AutoCC i1) (AutoCC i2) = i1 `compare` i2
301 cmp_kind (DictCC i1) (DictCC i2) = i1 `compare` i2
302 cmp_kind other_1     other_2
303   = let
304         tag1 = tag_CcKind other_1
305         tag2 = tag_CcKind other_2
306     in
307     if tag1 _LT_ tag2 then LT else GT
308   where
309     tag_CcKind (UserCC _) = (ILIT(1) :: FAST_INT)
310     tag_CcKind (AutoCC _) = ILIT(2)
311     tag_CcKind (DictCC _) = ILIT(3)
312
313 cmp_caf IsNotCafCC IsCafCC     = LT
314 cmp_caf IsNotCafCC IsNotCafCC  = EQ
315 cmp_caf IsCafCC    IsCafCC     = EQ
316 cmp_caf IsCafCC    IsNotCafCC  = GT
317 \end{code}
318
319 \begin{code}
320 showCostCentre    :: Bool -> CostCentre -> String
321 uppCostCentre     :: Bool -> CostCentre -> SDoc
322 uppCostCentreDecl :: Bool -> CostCentre -> SDoc
323
324 {-      PprUnfolding is gone now
325 showCostCentre PprUnfolding print_as_string cc
326   = ASSERT(not print_as_string) -- we never "print as string w/ Unfolding"
327     ASSERT(not (noCostCentreAttached cc))
328     ASSERT(not (currentOrSubsumedCosts cc))
329     uppShow 80 (upp_cc_uf cc)
330 -}
331
332 showCostCentre print_as_string cc
333   = showSDoc (uppCostCentre print_as_string cc)
334
335 uppCostCentre print_as_string NoCostCentre
336   | print_as_string     = text "\"NO_CC\""
337   | otherwise           = ptext SLIT("NO_CC")
338
339 uppCostCentre print_as_string SubsumedCosts
340   | print_as_string     = text "\"SUBSUMED\""
341   | otherwise           = ptext SLIT("CC_SUBSUMED")
342
343 uppCostCentre print_as_string CurrentCC
344   | print_as_string     = text "\"CURRENT_CC\""
345   | otherwise           = ptext SLIT("CCC")
346
347 uppCostCentre print_as_string OverheadCC
348   | print_as_string     = text "\"OVERHEAD\""
349   | otherwise           = ptext SLIT("CC_OVERHEAD")
350
351 uppCostCentre print_as_string cc
352   = getPprStyle $ \ sty ->
353     let
354         friendly_sty = userStyle sty || debugStyle sty    -- i.e. probably for human consumption
355         prefix_CC          = ptext SLIT("CC_")
356         basic_thing        = do_cc friendly_sty cc
357         basic_thing_string = stringToC basic_thing
358     in
359     if print_as_string then
360         hcat [char '"', text basic_thing_string, char '"']
361
362     else if friendly_sty then
363         text basic_thing
364     else
365         hcat [prefix_CC, identToC (_PK_ basic_thing)]
366   where
367     do_cc friendly_sty DontCareCC         = "DONT_CARE"
368     do_cc friendly_sty (AllCafsCC  m _)   = if print_as_string
369                                             then "CAFs_in_..."
370                                             else "CAFs." ++ _UNPK_ m
371     do_cc friendly_sty (AllDictsCC m _ d) = do_dupd friendly_sty d (
372                                             if print_as_string
373                                             then "DICTs_in_..."
374                                             else "DICTs." ++ _UNPK_ m)
375     do_cc friendly_sty PreludeCafsCC      = if print_as_string
376                                             then "CAFs_in_..."
377                                             else "CAFs"
378     do_cc friendly_sty (PreludeDictsCC d) = do_dupd friendly_sty d (
379                                             if print_as_string
380                                             then "DICTs_in_..."
381                                             else "DICTs")
382
383     do_cc friendly_sty (NormalCC kind mod_name grp_name is_dupd is_caf)
384       = let
385             basic_kind  = do_kind kind
386             module_kind = do_caf is_caf (moduleString mod_name ++ '/':
387                                                basic_kind)
388             grp_str   = if (_NULL_ grp_name) then mod_name else grp_name
389             full_kind = do_caf is_caf
390                          (moduleString mod_name  ++ 
391                           ('/' : _UNPK_ grp_str) ++ 
392                           ('/' : basic_kind))
393         in
394         if friendly_sty then
395            do_dupd friendly_sty is_dupd full_kind
396         else
397             module_kind
398       where
399         do_caf IsCafCC ls = "CAF:" ++ ls
400         do_caf _       ls = ls
401
402         do_kind (UserCC name) = _UNPK_ name
403         do_kind (AutoCC id)   = do_id id ++ (if friendly_sty then "/AUTO" else "")
404         do_kind (DictCC id)   = do_id id ++ (if friendly_sty then "/DICT" else "")
405
406         {-
407          do_id is only applied in a (not print_as_string) context for local ids,
408          hence using the occurrence name is enough.
409         -}
410         do_id :: Id -> String
411         do_id id = getOccString id
412
413     ---------------
414     do_dupd friendly_sty ADupdCC str = if friendly_sty then str ++ "/DUPD" else str
415     do_dupd _            _       str = str
416 \end{code}
417
418 Printing unfoldings is sufficiently weird that we do it separately.
419 This should only apply to CostCentres that can be ``set to'' (cf
420 @sccAbleCostCentre@).  That excludes CAFs and 
421 `overhead'---which are added at the very end---but includes dictionaries.
422 Dict \tr{_scc_}s may cross module boundaries to show ``scope'' info;
423 even if we won't ultimately do a \tr{SET_CCC} from it.
424 \begin{code}
425 upp_cc_uf (PreludeDictsCC d)
426   = hsep [ptext SLIT("_PRELUDE_DICTS_CC_"), upp_dupd d]
427 upp_cc_uf (AllDictsCC m g d)
428   = hsep [ptext SLIT("_ALL_DICTS_CC_"), 
429             char '"',ptext m,char '"',
430             char '"',ptext g,char '"',
431             upp_dupd d]
432
433 upp_cc_uf cc@(NormalCC cc_kind m g is_dupd is_caf)
434   = ASSERT(sccAbleCostCentre cc)
435     hsep [pp_kind cc_kind, 
436             char '"', ptext m, char '"', 
437             char '"', ptext g, char '"',
438             upp_dupd is_dupd, pp_caf is_caf]
439   where
440     pp_kind (UserCC name) = hcat [ptext SLIT("_USER_CC_ "), char '"', ptext name, char '"']
441     pp_kind (AutoCC id)   = (<>) (ptext SLIT("_AUTO_CC_ ")) (show_id id)
442     pp_kind (DictCC id)   = (<>) (ptext SLIT("_DICT_CC_ ")) (show_id id)
443
444     show_id id = pprIdInUnfolding {-no_in_scopes-} id
445
446     pp_caf IsCafCC    = ptext SLIT("_CAF_CC_")
447     pp_caf IsNotCafCC = ptext SLIT("_N_")
448
449 #ifdef DEBUG
450 upp_cc_uf other = panic ("upp_cc_uf:"++(showCostCentre True other))
451 #endif
452
453 upp_dupd AnOriginalCC = ptext SLIT("_N_")
454 upp_dupd ADupdCC      = ptext SLIT("_D_")
455 \end{code}
456
457 \begin{code}
458 uppCostCentreDecl is_local cc
459 #ifdef DEBUG
460   | noCostCentreAttached cc || currentOrSubsumedCosts cc
461   = panic "uppCostCentreDecl: no cost centre!"
462   | otherwise
463 #endif
464   = if is_local then
465         hcat [
466             ptext SLIT("CC_DECLARE"),char '(',
467             upp_ident, comma,
468             uppCostCentre True {-as String!-} cc, comma,
469             pp_str mod_name, comma,
470             pp_str grp_name, comma,
471             text is_subsumed, comma,
472             if externally_visible {- || all_toplev_ids_visible -}
473                         -- all_toplev stuff removed SLPJ Sept 97;
474                         -- not sure this is right.
475                then empty 
476                else ptext SLIT("static"),
477             text ");"]
478     else
479         hcat [ ptext SLIT("CC_EXTERN"),char '(', upp_ident, text ");" ]
480   where
481     upp_ident = uppCostCentre False{-as identifier!-} cc
482
483     pp_str s  = doubleQuotes (ptext s)
484
485     (mod_name, grp_name, is_subsumed, externally_visible)
486       = case cc of
487           AllCafsCC m g -> (m, g, cc_IS_CAF, True)
488
489           AllDictsCC m g _ -> (m, g, cc_IS_DICT, True)
490
491           NormalCC (DictCC i) m g is_dupd is_caf
492             -> (m, g, cc_IS_DICT, externallyVisibleId i)
493
494           NormalCC x m g is_dupd is_caf
495             -> (m, g, do_caf is_caf,
496                 case x of { UserCC _ -> True; AutoCC i -> externallyVisibleId i})
497       where
498         cc_IS_CAF      = "CC_IS_CAF"
499         cc_IS_DICT     = "CC_IS_DICT"
500         cc_IS_SUBSUMED = "CC_IS_SUBSUMED"
501         cc_IS_BORING   = "CC_IS_BORING"
502
503         do_caf IsCafCC       = cc_IS_CAF
504         do_caf IsNotCafCC    = cc_IS_BORING
505 \end{code}