Add a comment, connecting the seq to the test (#4367) that shows its usefulness
[ghc-hetmet.git] / compiler / basicTypes / IdInfo.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
4 %
5 \section[IdInfo]{@IdInfos@: Non-essential information about @Ids@}
6
7 (And a pretty good illustration of quite a few things wrong with
8 Haskell. [WDP 94/11])
9
10 \begin{code}
11 module IdInfo (
12         -- * The IdDetails type
13         IdDetails(..), pprIdDetails,
14
15         -- * The IdInfo type
16         IdInfo,         -- Abstract
17         vanillaIdInfo, noCafIdInfo,
18         seqIdInfo, megaSeqIdInfo,
19
20         -- ** Zapping various forms of Info
21         zapLamInfo, zapDemandInfo, zapFragileInfo,
22
23         -- ** The ArityInfo type
24         ArityInfo,
25         unknownArity, 
26         arityInfo, setArityInfo, ppArityInfo, 
27
28         -- ** Demand and strictness Info
29         strictnessInfo, setStrictnessInfo, 
30         demandInfo, setDemandInfo, pprStrictness,
31
32         -- ** Unfolding Info
33         unfoldingInfo, setUnfoldingInfo, setUnfoldingInfoLazily,
34
35         -- ** The InlinePragInfo type
36         InlinePragInfo,
37         inlinePragInfo, setInlinePragInfo,
38
39         -- ** The OccInfo type
40         OccInfo(..),
41         isDeadOcc, isLoopBreaker,
42         occInfo, setOccInfo,
43
44         InsideLam, OneBranch,
45         insideLam, notInsideLam, oneBranch, notOneBranch,
46         
47         -- ** The SpecInfo type
48         SpecInfo(..),
49         isEmptySpecInfo, specInfoFreeVars,
50         specInfoRules, seqSpecInfo, setSpecInfoHead,
51         specInfo, setSpecInfo,
52
53         -- ** The CAFInfo type
54         CafInfo(..),
55         ppCafInfo, mayHaveCafRefs,
56         cafInfo, setCafInfo,
57
58         -- ** The LBVarInfo type
59         LBVarInfo(..),
60         noLBVarInfo, hasNoLBVarInfo,
61         lbvarInfo, setLBVarInfo,
62
63         -- ** Tick-box Info
64         TickBoxOp(..), TickBoxId,
65     ) where
66
67 import CoreSyn
68
69 import Class
70 import PrimOp
71 import Name
72 import VarSet
73 import BasicTypes
74 import DataCon
75 import TyCon
76 import ForeignCall
77 import Demand
78 import Outputable       
79 import Module
80 import FastString
81
82 import Data.Maybe
83
84 -- infixl so you can say (id `set` a `set` b)
85 infixl  1 `setSpecInfo`,
86           `setArityInfo`,
87           `setInlinePragInfo`,
88           `setUnfoldingInfo`,
89           `setLBVarInfo`,
90           `setOccInfo`,
91           `setCafInfo`,
92           `setStrictnessInfo`,
93           `setDemandInfo`
94 \end{code}
95
96 %************************************************************************
97 %*                                                                      *
98                      IdDetails
99 %*                                                                      *
100 %************************************************************************
101
102 \begin{code}
103 -- | The 'IdDetails' of an 'Id' give stable, and necessary, 
104 -- information about the Id. 
105 data IdDetails
106   = VanillaId   
107
108   -- | The 'Id' for a record selector
109   | RecSelId                 
110     { sel_tycon   :: TyCon      -- ^ For a data type family, this is the /instance/ 'TyCon'
111                                 --   not the family 'TyCon'
112     , sel_naughty :: Bool       -- True <=> a "naughty" selector which can't actually exist, for example @x@ in:
113                                 --    data T = forall a. MkT { x :: a }
114     }                           -- See Note [Naughty record selectors] in TcTyClsDecls
115
116   | DataConWorkId DataCon       -- ^ The 'Id' is for a data constructor /worker/
117   | DataConWrapId DataCon       -- ^ The 'Id' is for a data constructor /wrapper/
118                                 
119                                 -- [the only reasons we need to know is so that
120                                 --  a) to support isImplicitId
121                                 --  b) when desugaring a RecordCon we can get 
122                                 --     from the Id back to the data con]
123
124   | ClassOpId Class             -- ^ The 'Id' is an superclass selector or class operation of a class
125
126   | PrimOpId PrimOp             -- ^ The 'Id' is for a primitive operator
127   | FCallId ForeignCall         -- ^ The 'Id' is for a foreign call
128
129   | TickBoxOpId TickBoxOp       -- ^ The 'Id' is for a HPC tick box (both traditional and binary)
130
131   | DFunId Bool                 -- ^ A dictionary function.  
132                                 --   True <=> the class has only one method, so may be 
133                                 --            implemented with a newtype, so it might be bad 
134                                 --            to be strict on this dictionary
135
136
137 instance Outputable IdDetails where
138     ppr = pprIdDetails
139
140 pprIdDetails :: IdDetails -> SDoc
141 pprIdDetails VanillaId = empty
142 pprIdDetails other     = brackets (pp other)
143  where
144    pp VanillaId         = panic "pprIdDetails"
145    pp (DataConWorkId _) = ptext (sLit "DataCon")
146    pp (DataConWrapId _) = ptext (sLit "DataConWrapper")
147    pp (ClassOpId {})    = ptext (sLit "ClassOp")
148    pp (PrimOpId _)      = ptext (sLit "PrimOp")
149    pp (FCallId _)       = ptext (sLit "ForeignCall")
150    pp (TickBoxOpId _)   = ptext (sLit "TickBoxOp")
151    pp (DFunId b)        = ptext (sLit "DFunId") <> 
152                             ppWhen b (ptext (sLit "(newtype)"))
153    pp (RecSelId { sel_naughty = is_naughty })
154                          = brackets $ ptext (sLit "RecSel") 
155                             <> ppWhen is_naughty (ptext (sLit "(naughty)"))
156 \end{code}
157
158
159 %************************************************************************
160 %*                                                                      *
161 \subsection{The main IdInfo type}
162 %*                                                                      *
163 %************************************************************************
164
165 \begin{code}
166 -- | An 'IdInfo' gives /optional/ information about an 'Id'.  If
167 -- present it never lies, but it may not be present, in which case there
168 -- is always a conservative assumption which can be made.
169 -- 
170 -- Two 'Id's may have different info even though they have the same
171 -- 'Unique' (and are hence the same 'Id'); for example, one might lack
172 -- the properties attached to the other.
173 -- 
174 -- The 'IdInfo' gives information about the value, or definition, of the
175 -- 'Id'.  It does not contain information about the 'Id''s usage,
176 -- except for 'demandInfo' and 'lbvarInfo'.
177 data IdInfo
178   = IdInfo {
179         arityInfo       :: !ArityInfo,          -- ^ 'Id' arity
180         specInfo        :: SpecInfo,            -- ^ Specialisations of the 'Id's function which exist
181                                                 -- See Note [Specialisations and RULES in IdInfo]
182         unfoldingInfo   :: Unfolding,           -- ^ The 'Id's unfolding
183         cafInfo         :: CafInfo,             -- ^ 'Id' CAF info
184         lbvarInfo       :: LBVarInfo,           -- ^ Info about a lambda-bound variable, if the 'Id' is one
185         inlinePragInfo  :: InlinePragma,        -- ^ Any inline pragma atached to the 'Id'
186         occInfo         :: OccInfo,             -- ^ How the 'Id' occurs in the program
187
188         strictnessInfo :: Maybe StrictSig,      -- ^ Id strictness information. Reason for Maybe: 
189                                                 -- the DmdAnal phase needs to know whether
190                                                 -- this is the first visit, so it can assign botSig.
191                                                 -- Other customers want topSig.  So @Nothing@ is good.
192
193         demandInfo        :: Maybe Demand       -- ^ Id demand information. Similarly we want to know 
194                                                 -- if there's no known demand yet, for when we are looking
195                                                 -- for CPR info
196     }
197
198 -- | Just evaluate the 'IdInfo' to WHNF
199 seqIdInfo :: IdInfo -> ()
200 seqIdInfo (IdInfo {}) = ()
201
202 -- | Evaluate all the fields of the 'IdInfo' that are generally demanded by the
203 -- compiler
204 megaSeqIdInfo :: IdInfo -> ()
205 megaSeqIdInfo info
206   = seqSpecInfo (specInfo info)                 `seq`
207
208 -- Omitting this improves runtimes a little, presumably because
209 -- some unfoldings are not calculated at all
210 --    seqUnfolding (unfoldingInfo info)         `seq`
211
212     seqDemandInfo (demandInfo info)     `seq`
213     seqStrictnessInfo (strictnessInfo info) `seq`
214
215     seqCaf (cafInfo info)                       `seq`
216     seqLBVar (lbvarInfo info)                   `seq`
217     seqOccInfo (occInfo info) 
218
219 seqStrictnessInfo :: Maybe StrictSig -> ()
220 seqStrictnessInfo Nothing = ()
221 seqStrictnessInfo (Just ty) = seqStrictSig ty
222
223 seqDemandInfo :: Maybe Demand -> ()
224 seqDemandInfo Nothing    = ()
225 seqDemandInfo (Just dmd) = seqDemand dmd
226 \end{code}
227
228 Setters
229
230 \begin{code}
231 setSpecInfo :: IdInfo -> SpecInfo -> IdInfo
232 setSpecInfo       info sp = sp `seq` info { specInfo = sp }
233 setInlinePragInfo :: IdInfo -> InlinePragma -> IdInfo
234 setInlinePragInfo info pr = pr `seq` info { inlinePragInfo = pr }
235 setOccInfo :: IdInfo -> OccInfo -> IdInfo
236 setOccInfo        info oc = oc `seq` info { occInfo = oc }
237         -- Try to avoid spack leaks by seq'ing
238
239 setUnfoldingInfoLazily :: IdInfo -> Unfolding -> IdInfo
240 setUnfoldingInfoLazily info uf  -- Lazy variant to avoid looking at the
241   =                             -- unfolding of an imported Id unless necessary
242     info { unfoldingInfo = uf } -- (In this case the demand-zapping is redundant.)
243
244 setUnfoldingInfo :: IdInfo -> Unfolding -> IdInfo
245 setUnfoldingInfo info uf 
246   = seqUnfolding uf `seq`       -- This seq makes a BIG difference to Trac #4367
247     info { unfoldingInfo = uf }
248
249 setArityInfo :: IdInfo -> ArityInfo -> IdInfo
250 setArityInfo      info ar  = info { arityInfo = ar  }
251 setCafInfo :: IdInfo -> CafInfo -> IdInfo
252 setCafInfo        info caf = info { cafInfo = caf }
253
254 setLBVarInfo :: IdInfo -> LBVarInfo -> IdInfo
255 setLBVarInfo      info lb = {-lb `seq`-} info { lbvarInfo = lb }
256
257 setDemandInfo :: IdInfo -> Maybe Demand -> IdInfo
258 setDemandInfo     info dd = dd `seq` info { demandInfo = dd }
259
260 setStrictnessInfo :: IdInfo -> Maybe StrictSig -> IdInfo
261 setStrictnessInfo info dd = dd `seq` info { strictnessInfo = dd }
262 \end{code}
263
264
265 \begin{code}
266 -- | Basic 'IdInfo' that carries no useful information whatsoever
267 vanillaIdInfo :: IdInfo
268 vanillaIdInfo 
269   = IdInfo {
270             cafInfo             = vanillaCafInfo,
271             arityInfo           = unknownArity,
272             specInfo            = emptySpecInfo,
273             unfoldingInfo       = noUnfolding,
274             lbvarInfo           = NoLBVarInfo,
275             inlinePragInfo      = defaultInlinePragma,
276             occInfo             = NoOccInfo,
277             demandInfo  = Nothing,
278             strictnessInfo   = Nothing
279            }
280
281 -- | More informative 'IdInfo' we can use when we know the 'Id' has no CAF references
282 noCafIdInfo :: IdInfo
283 noCafIdInfo  = vanillaIdInfo `setCafInfo`    NoCafRefs
284         -- Used for built-in type Ids in MkId.
285 \end{code}
286
287
288 %************************************************************************
289 %*                                                                      *
290 \subsection[arity-IdInfo]{Arity info about an @Id@}
291 %*                                                                      *
292 %************************************************************************
293
294 For locally-defined Ids, the code generator maintains its own notion
295 of their arities; so it should not be asking...  (but other things
296 besides the code-generator need arity info!)
297
298 \begin{code}
299 -- | An 'ArityInfo' of @n@ tells us that partial application of this 
300 -- 'Id' to up to @n-1@ value arguments does essentially no work.
301 --
302 -- That is not necessarily the same as saying that it has @n@ leading 
303 -- lambdas, because coerces may get in the way.
304 --
305 -- The arity might increase later in the compilation process, if
306 -- an extra lambda floats up to the binding site.
307 type ArityInfo = Arity
308
309 -- | It is always safe to assume that an 'Id' has an arity of 0
310 unknownArity :: Arity
311 unknownArity = 0 :: Arity
312
313 ppArityInfo :: Int -> SDoc
314 ppArityInfo 0 = empty
315 ppArityInfo n = hsep [ptext (sLit "Arity"), int n]
316 \end{code}
317
318 %************************************************************************
319 %*                                                                      *
320 \subsection{Inline-pragma information}
321 %*                                                                      *
322 %************************************************************************
323
324 \begin{code}
325 -- | Tells when the inlining is active.
326 -- When it is active the thing may be inlined, depending on how
327 -- big it is.
328 --
329 -- If there was an @INLINE@ pragma, then as a separate matter, the
330 -- RHS will have been made to look small with a Core inline 'Note'
331 --
332 -- The default 'InlinePragInfo' is 'AlwaysActive', so the info serves
333 -- entirely as a way to inhibit inlining until we want it
334 type InlinePragInfo = InlinePragma
335 \end{code}
336
337
338 %************************************************************************
339 %*                                                                      *
340                Strictness
341 %*                                                                      *
342 %************************************************************************
343
344 \begin{code}
345 pprStrictness :: Maybe StrictSig -> SDoc
346 pprStrictness Nothing    = empty
347 pprStrictness (Just sig) = ppr sig
348 \end{code}
349
350
351 %************************************************************************
352 %*                                                                      *
353         SpecInfo
354 %*                                                                      *
355 %************************************************************************
356
357 Note [Specialisations and RULES in IdInfo]
358 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
359 Generally speaking, a GlobalIdshas an *empty* SpecInfo.  All their
360 RULES are contained in the globally-built rule-base.  In principle,
361 one could attach the to M.f the RULES for M.f that are defined in M.
362 But we don't do that for instance declarations and so we just treat
363 them all uniformly.
364
365 The EXCEPTION is PrimOpIds, which do have rules in their IdInfo. That is
366 jsut for convenience really.
367
368 However, LocalIds may have non-empty SpecInfo.  We treat them 
369 differently because:
370   a) they might be nested, in which case a global table won't work
371   b) the RULE might mention free variables, which we use to keep things alive
372
373 In TidyPgm, when the LocalId becomes a GlobalId, its RULES are stripped off
374 and put in the global list.
375
376 \begin{code}
377 -- | Records the specializations of this 'Id' that we know about
378 -- in the form of rewrite 'CoreRule's that target them
379 data SpecInfo 
380   = SpecInfo 
381         [CoreRule] 
382         VarSet          -- Locally-defined free vars of *both* LHS and RHS 
383                         -- of rules.  I don't think it needs to include the
384                         -- ru_fn though.
385                         -- Note [Rule dependency info] in OccurAnal
386
387 -- | Assume that no specilizations exist: always safe
388 emptySpecInfo :: SpecInfo
389 emptySpecInfo = SpecInfo [] emptyVarSet
390
391 isEmptySpecInfo :: SpecInfo -> Bool
392 isEmptySpecInfo (SpecInfo rs _) = null rs
393
394 -- | Retrieve the locally-defined free variables of both the left and
395 -- right hand sides of the specialization rules
396 specInfoFreeVars :: SpecInfo -> VarSet
397 specInfoFreeVars (SpecInfo _ fvs) = fvs
398
399 specInfoRules :: SpecInfo -> [CoreRule]
400 specInfoRules (SpecInfo rules _) = rules
401
402 -- | Change the name of the function the rule is keyed on on all of the 'CoreRule's
403 setSpecInfoHead :: Name -> SpecInfo -> SpecInfo
404 setSpecInfoHead fn (SpecInfo rules fvs)
405   = SpecInfo (map (setRuleIdName fn) rules) fvs
406
407 seqSpecInfo :: SpecInfo -> ()
408 seqSpecInfo (SpecInfo rules fvs) = seqRules rules `seq` seqVarSet fvs
409 \end{code}
410
411 %************************************************************************
412 %*                                                                      *
413 \subsection[CG-IdInfo]{Code generator-related information}
414 %*                                                                      *
415 %************************************************************************
416
417 \begin{code}
418 -- CafInfo is used to build Static Reference Tables (see simplStg/SRT.lhs).
419
420 -- | Records whether an 'Id' makes Constant Applicative Form references
421 data CafInfo 
422         = MayHaveCafRefs                -- ^ Indicates that the 'Id' is for either:
423                                         --
424                                         -- 1. A function or static constructor
425                                         --    that refers to one or more CAFs, or
426                                         --
427                                         -- 2. A real live CAF
428
429         | NoCafRefs                     -- ^ A function or static constructor
430                                         -- that refers to no CAFs.
431         deriving (Eq, Ord)
432
433 -- | Assumes that the 'Id' has CAF references: definitely safe
434 vanillaCafInfo :: CafInfo
435 vanillaCafInfo = MayHaveCafRefs
436
437 mayHaveCafRefs :: CafInfo -> Bool
438 mayHaveCafRefs  MayHaveCafRefs = True
439 mayHaveCafRefs _               = False
440
441 seqCaf :: CafInfo -> ()
442 seqCaf c = c `seq` ()
443
444 instance Outputable CafInfo where
445    ppr = ppCafInfo
446
447 ppCafInfo :: CafInfo -> SDoc
448 ppCafInfo NoCafRefs = ptext (sLit "NoCafRefs")
449 ppCafInfo MayHaveCafRefs = empty
450 \end{code}
451
452 %************************************************************************
453 %*                                                                      *
454 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
455 %*                                                                      *
456 %************************************************************************
457
458 \begin{code}
459 -- | If the 'Id' is a lambda-bound variable then it may have lambda-bound
460 -- variable info. Sometimes we know whether the lambda binding this variable
461 -- is a \"one-shot\" lambda; that is, whether it is applied at most once.
462 --
463 -- This information may be useful in optimisation, as computations may
464 -- safely be floated inside such a lambda without risk of duplicating
465 -- work.
466 data LBVarInfo = NoLBVarInfo            -- ^ No information
467                | IsOneShotLambda        -- ^ The lambda is applied at most once).
468
469 -- | It is always safe to assume that an 'Id' has no lambda-bound variable information
470 noLBVarInfo :: LBVarInfo
471 noLBVarInfo = NoLBVarInfo
472
473 hasNoLBVarInfo :: LBVarInfo -> Bool
474 hasNoLBVarInfo NoLBVarInfo     = True
475 hasNoLBVarInfo IsOneShotLambda = False
476
477 seqLBVar :: LBVarInfo -> ()
478 seqLBVar l = l `seq` ()
479
480 pprLBVarInfo :: LBVarInfo -> SDoc
481 pprLBVarInfo NoLBVarInfo     = empty
482 pprLBVarInfo IsOneShotLambda = ptext (sLit "OneShot")
483
484 instance Outputable LBVarInfo where
485     ppr = pprLBVarInfo
486
487 instance Show LBVarInfo where
488     showsPrec p c = showsPrecSDoc p (ppr c)
489 \end{code}
490
491
492 %************************************************************************
493 %*                                                                      *
494 \subsection{Bulk operations on IdInfo}
495 %*                                                                      *
496 %************************************************************************
497
498 \begin{code}
499 -- | This is used to remove information on lambda binders that we have
500 -- setup as part of a lambda group, assuming they will be applied all at once,
501 -- but turn out to be part of an unsaturated lambda as in e.g:
502 --
503 -- > (\x1. \x2. e) arg1
504 zapLamInfo :: IdInfo -> Maybe IdInfo
505 zapLamInfo info@(IdInfo {occInfo = occ, demandInfo = demand})
506   | is_safe_occ occ && is_safe_dmd demand
507   = Nothing
508   | otherwise
509   = Just (info {occInfo = safe_occ, demandInfo = Nothing})
510   where
511         -- The "unsafe" occ info is the ones that say I'm not in a lambda
512         -- because that might not be true for an unsaturated lambda
513     is_safe_occ (OneOcc in_lam _ _) = in_lam
514     is_safe_occ _other              = True
515
516     safe_occ = case occ of
517                  OneOcc _ once int_cxt -> OneOcc insideLam once int_cxt
518                  _other                -> occ
519
520     is_safe_dmd Nothing    = True
521     is_safe_dmd (Just dmd) = not (isStrictDmd dmd)
522 \end{code}
523
524 \begin{code}
525 -- | Remove demand info on the 'IdInfo' if it is present, otherwise return @Nothing@
526 zapDemandInfo :: IdInfo -> Maybe IdInfo
527 zapDemandInfo info@(IdInfo {demandInfo = dmd})
528   | isJust dmd = Just (info {demandInfo = Nothing})
529   | otherwise  = Nothing
530 \end{code}
531
532 \begin{code}
533 zapFragileInfo :: IdInfo -> Maybe IdInfo
534 -- ^ Zap info that depends on free variables
535 zapFragileInfo info 
536   = Just (info `setSpecInfo` emptySpecInfo
537                `setUnfoldingInfo` noUnfolding
538                `setOccInfo` zapFragileOcc occ)
539   where
540     occ = occInfo info
541 \end{code}
542
543 %************************************************************************
544 %*                                                                      *
545 \subsection{TickBoxOp}
546 %*                                                                      *
547 %************************************************************************
548
549 \begin{code}
550 type TickBoxId = Int
551
552 -- | Tick box for Hpc-style coverage
553 data TickBoxOp 
554    = TickBox Module {-# UNPACK #-} !TickBoxId
555
556 instance Outputable TickBoxOp where
557     ppr (TickBox mod n)         = ptext (sLit "tick") <+> ppr (mod,n)
558 \end{code}