9dda37e46919ede4e55917fc2a1b4e5add4b3587
[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   = -- We don't seq the unfolding, as we generate intermediate
247     -- unfoldings which are just thrown away, so evaluating them is a
248     -- waste of time.
249     -- seqUnfolding uf `seq`
250     info { unfoldingInfo = uf }
251
252 setArityInfo :: IdInfo -> ArityInfo -> IdInfo
253 setArityInfo      info ar  = info { arityInfo = ar  }
254 setCafInfo :: IdInfo -> CafInfo -> IdInfo
255 setCafInfo        info caf = info { cafInfo = caf }
256
257 setLBVarInfo :: IdInfo -> LBVarInfo -> IdInfo
258 setLBVarInfo      info lb = {-lb `seq`-} info { lbvarInfo = lb }
259
260 setDemandInfo :: IdInfo -> Maybe Demand -> IdInfo
261 setDemandInfo     info dd = dd `seq` info { demandInfo = dd }
262
263 setStrictnessInfo :: IdInfo -> Maybe StrictSig -> IdInfo
264 setStrictnessInfo info dd = dd `seq` info { strictnessInfo = dd }
265 \end{code}
266
267
268 \begin{code}
269 -- | Basic 'IdInfo' that carries no useful information whatsoever
270 vanillaIdInfo :: IdInfo
271 vanillaIdInfo 
272   = IdInfo {
273             cafInfo             = vanillaCafInfo,
274             arityInfo           = unknownArity,
275             specInfo            = emptySpecInfo,
276             unfoldingInfo       = noUnfolding,
277             lbvarInfo           = NoLBVarInfo,
278             inlinePragInfo      = defaultInlinePragma,
279             occInfo             = NoOccInfo,
280             demandInfo  = Nothing,
281             strictnessInfo   = Nothing
282            }
283
284 -- | More informative 'IdInfo' we can use when we know the 'Id' has no CAF references
285 noCafIdInfo :: IdInfo
286 noCafIdInfo  = vanillaIdInfo `setCafInfo`    NoCafRefs
287         -- Used for built-in type Ids in MkId.
288 \end{code}
289
290
291 %************************************************************************
292 %*                                                                      *
293 \subsection[arity-IdInfo]{Arity info about an @Id@}
294 %*                                                                      *
295 %************************************************************************
296
297 For locally-defined Ids, the code generator maintains its own notion
298 of their arities; so it should not be asking...  (but other things
299 besides the code-generator need arity info!)
300
301 \begin{code}
302 -- | An 'ArityInfo' of @n@ tells us that partial application of this 
303 -- 'Id' to up to @n-1@ value arguments does essentially no work.
304 --
305 -- That is not necessarily the same as saying that it has @n@ leading 
306 -- lambdas, because coerces may get in the way.
307 --
308 -- The arity might increase later in the compilation process, if
309 -- an extra lambda floats up to the binding site.
310 type ArityInfo = Arity
311
312 -- | It is always safe to assume that an 'Id' has an arity of 0
313 unknownArity :: Arity
314 unknownArity = 0 :: Arity
315
316 ppArityInfo :: Int -> SDoc
317 ppArityInfo 0 = empty
318 ppArityInfo n = hsep [ptext (sLit "Arity"), int n]
319 \end{code}
320
321 %************************************************************************
322 %*                                                                      *
323 \subsection{Inline-pragma information}
324 %*                                                                      *
325 %************************************************************************
326
327 \begin{code}
328 -- | Tells when the inlining is active.
329 -- When it is active the thing may be inlined, depending on how
330 -- big it is.
331 --
332 -- If there was an @INLINE@ pragma, then as a separate matter, the
333 -- RHS will have been made to look small with a Core inline 'Note'
334 --
335 -- The default 'InlinePragInfo' is 'AlwaysActive', so the info serves
336 -- entirely as a way to inhibit inlining until we want it
337 type InlinePragInfo = InlinePragma
338 \end{code}
339
340
341 %************************************************************************
342 %*                                                                      *
343                Strictness
344 %*                                                                      *
345 %************************************************************************
346
347 \begin{code}
348 pprStrictness :: Maybe StrictSig -> SDoc
349 pprStrictness Nothing    = empty
350 pprStrictness (Just sig) = ppr sig
351 \end{code}
352
353
354 %************************************************************************
355 %*                                                                      *
356         SpecInfo
357 %*                                                                      *
358 %************************************************************************
359
360 Note [Specialisations and RULES in IdInfo]
361 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
362 Generally speaking, a GlobalIdshas an *empty* SpecInfo.  All their
363 RULES are contained in the globally-built rule-base.  In principle,
364 one could attach the to M.f the RULES for M.f that are defined in M.
365 But we don't do that for instance declarations and so we just treat
366 them all uniformly.
367
368 The EXCEPTION is PrimOpIds, which do have rules in their IdInfo. That is
369 jsut for convenience really.
370
371 However, LocalIds may have non-empty SpecInfo.  We treat them 
372 differently because:
373   a) they might be nested, in which case a global table won't work
374   b) the RULE might mention free variables, which we use to keep things alive
375
376 In TidyPgm, when the LocalId becomes a GlobalId, its RULES are stripped off
377 and put in the global list.
378
379 \begin{code}
380 -- | Records the specializations of this 'Id' that we know about
381 -- in the form of rewrite 'CoreRule's that target them
382 data SpecInfo 
383   = SpecInfo 
384         [CoreRule] 
385         VarSet          -- Locally-defined free vars of *both* LHS and RHS 
386                         -- of rules.  I don't think it needs to include the
387                         -- ru_fn though.
388                         -- Note [Rule dependency info] in OccurAnal
389
390 -- | Assume that no specilizations exist: always safe
391 emptySpecInfo :: SpecInfo
392 emptySpecInfo = SpecInfo [] emptyVarSet
393
394 isEmptySpecInfo :: SpecInfo -> Bool
395 isEmptySpecInfo (SpecInfo rs _) = null rs
396
397 -- | Retrieve the locally-defined free variables of both the left and
398 -- right hand sides of the specialization rules
399 specInfoFreeVars :: SpecInfo -> VarSet
400 specInfoFreeVars (SpecInfo _ fvs) = fvs
401
402 specInfoRules :: SpecInfo -> [CoreRule]
403 specInfoRules (SpecInfo rules _) = rules
404
405 -- | Change the name of the function the rule is keyed on on all of the 'CoreRule's
406 setSpecInfoHead :: Name -> SpecInfo -> SpecInfo
407 setSpecInfoHead fn (SpecInfo rules fvs)
408   = SpecInfo (map (setRuleIdName fn) rules) fvs
409
410 seqSpecInfo :: SpecInfo -> ()
411 seqSpecInfo (SpecInfo rules fvs) = seqRules rules `seq` seqVarSet fvs
412 \end{code}
413
414 %************************************************************************
415 %*                                                                      *
416 \subsection[CG-IdInfo]{Code generator-related information}
417 %*                                                                      *
418 %************************************************************************
419
420 \begin{code}
421 -- CafInfo is used to build Static Reference Tables (see simplStg/SRT.lhs).
422
423 -- | Records whether an 'Id' makes Constant Applicative Form references
424 data CafInfo 
425         = MayHaveCafRefs                -- ^ Indicates that the 'Id' is for either:
426                                         --
427                                         -- 1. A function or static constructor
428                                         --    that refers to one or more CAFs, or
429                                         --
430                                         -- 2. A real live CAF
431
432         | NoCafRefs                     -- ^ A function or static constructor
433                                         -- that refers to no CAFs.
434         deriving (Eq, Ord)
435
436 -- | Assumes that the 'Id' has CAF references: definitely safe
437 vanillaCafInfo :: CafInfo
438 vanillaCafInfo = MayHaveCafRefs
439
440 mayHaveCafRefs :: CafInfo -> Bool
441 mayHaveCafRefs  MayHaveCafRefs = True
442 mayHaveCafRefs _               = False
443
444 seqCaf :: CafInfo -> ()
445 seqCaf c = c `seq` ()
446
447 instance Outputable CafInfo where
448    ppr = ppCafInfo
449
450 ppCafInfo :: CafInfo -> SDoc
451 ppCafInfo NoCafRefs = ptext (sLit "NoCafRefs")
452 ppCafInfo MayHaveCafRefs = empty
453 \end{code}
454
455 %************************************************************************
456 %*                                                                      *
457 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
458 %*                                                                      *
459 %************************************************************************
460
461 \begin{code}
462 -- | If the 'Id' is a lambda-bound variable then it may have lambda-bound
463 -- variable info. Sometimes we know whether the lambda binding this variable
464 -- is a \"one-shot\" lambda; that is, whether it is applied at most once.
465 --
466 -- This information may be useful in optimisation, as computations may
467 -- safely be floated inside such a lambda without risk of duplicating
468 -- work.
469 data LBVarInfo = NoLBVarInfo            -- ^ No information
470                | IsOneShotLambda        -- ^ The lambda is applied at most once).
471
472 -- | It is always safe to assume that an 'Id' has no lambda-bound variable information
473 noLBVarInfo :: LBVarInfo
474 noLBVarInfo = NoLBVarInfo
475
476 hasNoLBVarInfo :: LBVarInfo -> Bool
477 hasNoLBVarInfo NoLBVarInfo     = True
478 hasNoLBVarInfo IsOneShotLambda = False
479
480 seqLBVar :: LBVarInfo -> ()
481 seqLBVar l = l `seq` ()
482
483 pprLBVarInfo :: LBVarInfo -> SDoc
484 pprLBVarInfo NoLBVarInfo     = empty
485 pprLBVarInfo IsOneShotLambda = ptext (sLit "OneShot")
486
487 instance Outputable LBVarInfo where
488     ppr = pprLBVarInfo
489
490 instance Show LBVarInfo where
491     showsPrec p c = showsPrecSDoc p (ppr c)
492 \end{code}
493
494
495 %************************************************************************
496 %*                                                                      *
497 \subsection{Bulk operations on IdInfo}
498 %*                                                                      *
499 %************************************************************************
500
501 \begin{code}
502 -- | This is used to remove information on lambda binders that we have
503 -- setup as part of a lambda group, assuming they will be applied all at once,
504 -- but turn out to be part of an unsaturated lambda as in e.g:
505 --
506 -- > (\x1. \x2. e) arg1
507 zapLamInfo :: IdInfo -> Maybe IdInfo
508 zapLamInfo info@(IdInfo {occInfo = occ, demandInfo = demand})
509   | is_safe_occ occ && is_safe_dmd demand
510   = Nothing
511   | otherwise
512   = Just (info {occInfo = safe_occ, demandInfo = Nothing})
513   where
514         -- The "unsafe" occ info is the ones that say I'm not in a lambda
515         -- because that might not be true for an unsaturated lambda
516     is_safe_occ (OneOcc in_lam _ _) = in_lam
517     is_safe_occ _other              = True
518
519     safe_occ = case occ of
520                  OneOcc _ once int_cxt -> OneOcc insideLam once int_cxt
521                  _other                -> occ
522
523     is_safe_dmd Nothing    = True
524     is_safe_dmd (Just dmd) = not (isStrictDmd dmd)
525 \end{code}
526
527 \begin{code}
528 -- | Remove demand info on the 'IdInfo' if it is present, otherwise return @Nothing@
529 zapDemandInfo :: IdInfo -> Maybe IdInfo
530 zapDemandInfo info@(IdInfo {demandInfo = dmd})
531   | isJust dmd = Just (info {demandInfo = Nothing})
532   | otherwise  = Nothing
533 \end{code}
534
535 \begin{code}
536 zapFragileInfo :: IdInfo -> Maybe IdInfo
537 -- ^ Zap info that depends on free variables
538 zapFragileInfo info 
539   = Just (info `setSpecInfo` emptySpecInfo
540                `setUnfoldingInfo` noUnfolding
541                `setOccInfo` zapFragileOcc occ)
542   where
543     occ = occInfo info
544 \end{code}
545
546 %************************************************************************
547 %*                                                                      *
548 \subsection{TickBoxOp}
549 %*                                                                      *
550 %************************************************************************
551
552 \begin{code}
553 type TickBoxId = Int
554
555 -- | Tick box for Hpc-style coverage
556 data TickBoxOp 
557    = TickBox Module {-# UNPACK #-} !TickBoxId
558
559 instance Outputable TickBoxOp where
560     ppr (TickBox mod n)         = ptext (sLit "tick") <+> ppr (mod,n)
561 \end{code}