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