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