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