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