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