[project @ 2000-11-14 10:46:39 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / IdInfo.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
3 %
4 \section[IdInfo]{@IdInfos@: Non-essential information about @Ids@}
5
6 (And a pretty good illustration of quite a few things wrong with
7 Haskell. [WDP 94/11])
8
9 \begin{code}
10 module IdInfo (
11         IdInfo,         -- Abstract
12
13         vanillaIdInfo, constantIdInfo, mkIdInfo, seqIdInfo, megaSeqIdInfo,
14
15         -- Zapping
16         zapFragileInfo, zapLamInfo, zapSpecPragInfo, shortableIdInfo, copyIdInfo,
17
18         -- Flavour
19         IdFlavour(..), flavourInfo, 
20         setNoDiscardInfo, setFlavourInfo,
21         ppFlavourInfo,
22
23         -- Arity
24         ArityInfo(..),
25         exactArity, atLeastArity, unknownArity, hasArity,
26         arityInfo, setArityInfo, ppArityInfo, arityLowerBound,
27
28         -- Strictness; imported from Demand
29         StrictnessInfo(..),
30         mkStrictnessInfo, noStrictnessInfo,
31         ppStrictnessInfo,isBottomingStrictness, 
32         strictnessInfo, setStrictnessInfo,      
33
34         -- Usage generalisation
35         TyGenInfo(..),
36         tyGenInfo, setTyGenInfo,
37         noTyGenInfo, isNoTyGenInfo, ppTyGenInfo, tyGenInfoString,
38
39         -- Worker
40         WorkerInfo(..), workerExists, wrapperArity, workerId,
41         workerInfo, setWorkerInfo, ppWorkerInfo,
42
43         -- Unfolding
44         unfoldingInfo, setUnfoldingInfo, 
45
46         -- DemandInfo
47         demandInfo, setDemandInfo, 
48
49         -- Inline prags
50         InlinePragInfo(..), 
51         inlinePragInfo, setInlinePragInfo, pprInlinePragInfo,
52         isNeverInlinePrag, neverInlinePrag,
53
54         -- Occurrence info
55         OccInfo(..), isFragileOcc, isDeadOcc, isLoopBreaker,
56         InsideLam, OneBranch, insideLam, notInsideLam, oneBranch, notOneBranch,
57         occInfo, setOccInfo, 
58
59         -- Specialisation
60         specInfo, setSpecInfo,
61
62         -- CAF info
63         CafInfo(..), cafInfo, setCafInfo, ppCafInfo,
64
65         -- Constructed Product Result Info
66         CprInfo(..), cprInfo, setCprInfo, ppCprInfo, noCprInfo,
67
68         -- Lambda-bound variable info
69         LBVarInfo(..), lbvarInfo, setLBVarInfo, noLBVarInfo
70     ) where
71
72 #include "HsVersions.h"
73
74
75 import CoreSyn
76 import Type             ( Type, usOnce )
77 import PrimOp           ( PrimOp )
78 import Var              ( Id )
79 import BasicTypes       ( OccInfo(..), isFragileOcc, isDeadOcc, seqOccInfo, isLoopBreaker,
80                           InsideLam, insideLam, notInsideLam, 
81                           OneBranch, oneBranch, notOneBranch,
82                           Arity
83                         )
84 import DataCon          ( DataCon )
85 import FieldLabel       ( FieldLabel )
86 import Type             ( usOnce, usMany )
87 import Demand           -- Lots of stuff
88 import Outputable       
89 import Util             ( seqList )
90
91 infixl  1 `setDemandInfo`,
92           `setTyGenInfo`,
93           `setStrictnessInfo`,
94           `setSpecInfo`,
95           `setArityInfo`,
96           `setInlinePragInfo`,
97           `setUnfoldingInfo`,
98           `setCprInfo`,
99           `setWorkerInfo`,
100           `setLBVarInfo`,
101           `setCafInfo`,
102           `setOccInfo`
103         -- infixl so you can say (id `set` a `set` b)
104 \end{code}
105
106 An @IdInfo@ gives {\em optional} information about an @Id@.  If
107 present it never lies, but it may not be present, in which case there
108 is always a conservative assumption which can be made.
109
110         There is one exception: the 'flavour' is *not* optional.
111         You must not discard it.
112         It used to be in Var.lhs, but that seems unclean.
113
114 Two @Id@s may have different info even though they have the same
115 @Unique@ (and are hence the same @Id@); for example, one might lack
116 the properties attached to the other.
117
118 The @IdInfo@ gives information about the value, or definition, of the
119 @Id@.  It does {\em not} contain information about the @Id@'s usage
120 (except for @DemandInfo@? ToDo). (@lbvarInfo@ is also a marginal
121 case.  KSW 1999-04).
122
123 \begin{code}
124 data IdInfo
125   = IdInfo {
126         flavourInfo     :: IdFlavour,           -- NOT OPTIONAL
127         arityInfo       :: ArityInfo,           -- Its arity
128         demandInfo      :: Demand,              -- Whether or not it is definitely demanded
129         specInfo        :: CoreRules,           -- Specialisations of this function which exist
130         tyGenInfo       :: TyGenInfo,           -- Restrictions on usage-generalisation of this Id
131         strictnessInfo  :: StrictnessInfo,      -- Strictness properties
132         workerInfo      :: WorkerInfo,          -- Pointer to Worker Function
133         unfoldingInfo   :: Unfolding,           -- Its unfolding
134         cafInfo         :: CafInfo,
135         cprInfo         :: CprInfo,             -- Function always constructs a product result
136         lbvarInfo       :: LBVarInfo,           -- Info about a lambda-bound variable
137         inlinePragInfo  :: InlinePragInfo,      -- Inline pragma
138         occInfo         :: OccInfo              -- How it occurs
139     }
140
141 seqIdInfo :: IdInfo -> ()
142 seqIdInfo (IdInfo {}) = ()
143
144 megaSeqIdInfo :: IdInfo -> ()
145 megaSeqIdInfo info
146   = seqFlavour (flavourInfo info)               `seq`
147     seqArity (arityInfo info)                   `seq`
148     seqDemand (demandInfo info)                 `seq`
149     seqRules (specInfo info)                    `seq`
150     seqTyGenInfo (tyGenInfo info)               `seq`
151     seqStrictnessInfo (strictnessInfo info)     `seq`
152     seqWorker (workerInfo info)                 `seq`
153
154 --    seqUnfolding (unfoldingInfo info) `seq`
155 -- Omitting this improves runtimes a little, presumably because
156 -- some unfoldings are not calculated at all
157
158     seqCaf (cafInfo info)               `seq`
159     seqCpr (cprInfo info)               `seq`
160     seqLBVar (lbvarInfo info)           `seq`
161     seqOccInfo (occInfo info) 
162 \end{code}
163
164 Setters
165
166 \begin{code}
167 setFlavourInfo    info fl = fl `seq` info { flavourInfo = fl }
168 setWorkerInfo     info wk = wk `seq` info { workerInfo = wk }
169 setSpecInfo       info sp = PSEQ sp (info { specInfo = sp })
170 setTyGenInfo      info tg = tg `seq` info { tyGenInfo = tg }
171 setInlinePragInfo info pr = pr `seq` info { inlinePragInfo = pr }
172 setOccInfo        info oc = oc `seq` info { occInfo = oc }
173 setStrictnessInfo info st = st `seq` info { strictnessInfo = st }
174         -- Try to avoid spack leaks by seq'ing
175
176 setUnfoldingInfo  info uf 
177   | isEvaldUnfolding uf && isStrict (demandInfo info)
178         -- If the unfolding is a value, the demand info may
179         -- go pear-shaped, so we nuke it.  Example:
180         --      let x = (a,b) in
181         --      case x of (p,q) -> h p q x
182         -- Here x is certainly demanded. But after we've nuked
183         -- the case, we'll get just
184         --      let x = (a,b) in h a b x
185         -- and now x is not demanded (I'm assuming h is lazy)
186         -- This really happens.  The solution here is a bit ad hoc...
187   = info { unfoldingInfo = uf, demandInfo = wwLazy }
188
189   | otherwise
190         -- We do *not* seq on the unfolding info, For some reason, doing so 
191         -- actually increases residency significantly. 
192   = info { unfoldingInfo = uf }
193
194 setDemandInfo     info dd = info { demandInfo = dd }
195 setArityInfo      info ar = info { arityInfo = ar  }
196 setCafInfo        info cf = info { cafInfo = cf }
197 setCprInfo        info cp = info { cprInfo = cp }
198 setLBVarInfo      info lb = info { lbvarInfo = lb }
199
200 setNoDiscardInfo  info = case flavourInfo info of
201                                 VanillaId -> info { flavourInfo = ExportedId }
202                                 other     -> info
203 zapSpecPragInfo   info = case flavourInfo info of
204                                 SpecPragmaId -> info { flavourInfo = VanillaId }
205                                 other        -> info
206 \end{code}
207
208
209 \begin{code}
210 vanillaIdInfo :: IdInfo
211 vanillaIdInfo = mkIdInfo VanillaId
212
213 constantIdInfo :: IdInfo
214 constantIdInfo = mkIdInfo ConstantId
215
216 mkIdInfo :: IdFlavour -> IdInfo
217 mkIdInfo flv = IdInfo {
218                     flavourInfo         = flv,
219                     arityInfo           = UnknownArity,
220                     demandInfo          = wwLazy,
221                     specInfo            = emptyCoreRules,
222                     tyGenInfo           = noTyGenInfo,
223                     workerInfo          = NoWorker,
224                     strictnessInfo      = NoStrictnessInfo,
225                     unfoldingInfo       = noUnfolding,
226                     cafInfo             = MayHaveCafRefs,
227                     cprInfo             = NoCPRInfo,
228                     lbvarInfo           = NoLBVarInfo,
229                     inlinePragInfo      = NoInlinePragInfo,
230                     occInfo             = NoOccInfo
231            }
232 \end{code}
233
234
235 %************************************************************************
236 %*                                                                      *
237 \subsection{Flavour}
238 %*                                                                      *
239 %************************************************************************
240
241 \begin{code}
242 data IdFlavour
243   = VanillaId                   -- Locally defined, not exported
244   | ExportedId                  -- Locally defined, exported
245   | SpecPragmaId                -- Locally defined, RHS holds specialised call
246
247   | ConstantId                  -- Imported from elsewhere, or a dictionary function,
248                                 -- default method Id.
249
250   | DataConId DataCon           -- The Id for a data constructor *worker*
251   | DataConWrapId DataCon       -- The Id for a data constructor *wrapper*
252                                 -- [the only reasons we need to know is so that
253                                 --  a) we can  suppress printing a definition in the interface file
254                                 --  b) when typechecking a pattern we can get from the
255                                 --     Id back to the data con]
256   | PrimOpId PrimOp             -- The Id for a primitive operator
257   | RecordSelId FieldLabel      -- The Id for a record selector
258
259
260 ppFlavourInfo :: IdFlavour -> SDoc
261 ppFlavourInfo VanillaId         = empty
262 ppFlavourInfo ExportedId        = ptext SLIT("[Exported]")
263 ppFlavourInfo SpecPragmaId      = ptext SLIT("[SpecPrag]")
264 ppFlavourInfo ConstantId        = ptext SLIT("[Constant]")
265 ppFlavourInfo (DataConId _)     = ptext SLIT("[DataCon]")
266 ppFlavourInfo (DataConWrapId _) = ptext SLIT("[DataConWrapper]")
267 ppFlavourInfo (PrimOpId _)      = ptext SLIT("[PrimOp]")
268 ppFlavourInfo (RecordSelId _)   = ptext SLIT("[RecSel]")
269
270 seqFlavour :: IdFlavour -> ()
271 seqFlavour f = f `seq` ()
272 \end{code}
273
274 The @SpecPragmaId@ exists only to make Ids that are
275 on the *LHS* of bindings created by SPECIALISE pragmas; 
276 eg:             s = f Int d
277 The SpecPragmaId is never itself mentioned; it
278 exists solely so that the specialiser will find
279 the call to f, and make specialised version of it.
280 The SpecPragmaId binding is discarded by the specialiser
281 when it gathers up overloaded calls.
282 Meanwhile, it is not discarded as dead code.
283
284
285 %************************************************************************
286 %*                                                                      *
287 \subsection[arity-IdInfo]{Arity info about an @Id@}
288 %*                                                                      *
289 %************************************************************************
290
291 For locally-defined Ids, the code generator maintains its own notion
292 of their arities; so it should not be asking...  (but other things
293 besides the code-generator need arity info!)
294
295 \begin{code}
296 data ArityInfo
297   = UnknownArity        -- No idea
298
299   | ArityExactly Arity  -- Arity is exactly this.  We use this when importing a
300                         -- function; it's already been compiled and we know its
301                         -- arity for sure.
302
303   | ArityAtLeast Arity  -- A partial application of this Id to up to n-1 value arguments
304                         -- does essentially no work.  That is not necessarily the
305                         -- same as saying that it has n leading lambdas, because coerces
306                         -- may get in the way.
307
308                         -- functions in the module being compiled.  Their arity
309                         -- might increase later in the compilation process, if
310                         -- an extra lambda floats up to the binding site.
311   deriving( Eq )
312
313 seqArity :: ArityInfo -> ()
314 seqArity a = arityLowerBound a `seq` ()
315
316 exactArity   = ArityExactly
317 atLeastArity = ArityAtLeast
318 unknownArity = UnknownArity
319
320 arityLowerBound :: ArityInfo -> Arity
321 arityLowerBound UnknownArity     = 0
322 arityLowerBound (ArityAtLeast n) = n
323 arityLowerBound (ArityExactly n) = n
324
325 hasArity :: ArityInfo -> Bool
326 hasArity UnknownArity = False
327 hasArity other        = True
328
329 ppArityInfo UnknownArity         = empty
330 ppArityInfo (ArityExactly arity) = hsep [ptext SLIT("__A"), int arity]
331 ppArityInfo (ArityAtLeast arity) = hsep [ptext SLIT("__AL"), int arity]
332 \end{code}
333
334 %************************************************************************
335 %*                                                                      *
336 \subsection{Inline-pragma information}
337 %*                                                                      *
338 %************************************************************************
339
340 \begin{code}
341 data InlinePragInfo
342   = NoInlinePragInfo
343   | IMustNotBeINLINEd Bool              -- True <=> came from an INLINE prag, False <=> came from a NOINLINE prag
344                       (Maybe Int)       -- Phase number from pragma, if any
345   deriving( Eq )
346         -- The True, Nothing case doesn't need to be recorded
347
348         -- SEE COMMENTS WITH CoreUnfold.blackListed on the
349         -- exact significance of the IMustNotBeINLINEd pragma
350
351 isNeverInlinePrag :: InlinePragInfo -> Bool
352 isNeverInlinePrag (IMustNotBeINLINEd _ Nothing) = True
353 isNeverInlinePrag other                         = False
354
355 neverInlinePrag :: InlinePragInfo
356 neverInlinePrag = IMustNotBeINLINEd True{-should be False? --SDM -} Nothing
357
358 instance Outputable InlinePragInfo where
359   -- This is now parsed in interface files
360   ppr NoInlinePragInfo = empty
361   ppr other_prag       = ptext SLIT("__U") <> pprInlinePragInfo other_prag
362
363 pprInlinePragInfo NoInlinePragInfo                   = empty
364 pprInlinePragInfo (IMustNotBeINLINEd True Nothing)   = empty
365 pprInlinePragInfo (IMustNotBeINLINEd True (Just n))  = brackets (int n)
366 pprInlinePragInfo (IMustNotBeINLINEd False Nothing)  = brackets (char '!')
367 pprInlinePragInfo (IMustNotBeINLINEd False (Just n)) = brackets (char '!' <> int n)
368                                                         
369 instance Show InlinePragInfo where
370   showsPrec p prag = showsPrecSDoc p (ppr prag)
371 \end{code}
372
373
374 %************************************************************************
375 %*                                                                    *
376 \subsection[TyGen-IdInfo]{Type generalisation info about an @Id@}
377 %*                                                                    *
378 %************************************************************************
379
380 Certain passes (notably usage inference) may change the type of an
381 identifier, modifying all in-scope uses of that identifier
382 appropriately to maintain type safety.
383
384 However, some identifiers must not have their types changed in this
385 way, because their types are conjured up in the front end of the
386 compiler rather than being read from the interface file.  Default
387 methods, dictionary functions, record selectors, and others are in
388 this category.  (see comment at TcClassDcl.tcClassSig).
389
390 To indicate this property, such identifiers are marked TyGenNever.
391
392 Furthermore, if the usage inference generates a usage-specialised
393 variant of a function, we must NOT re-infer a fully-generalised type
394 at the next inference.  This finer property is indicated by a
395 TyGenUInfo on the identifier.
396
397 \begin{code}
398 data TyGenInfo
399   = NoTyGenInfo              -- no restriction on type generalisation
400
401   | TyGenUInfo [Maybe Type]  -- restrict generalisation of this Id to
402                              -- preserve specified usage annotations
403
404   | TyGenNever               -- never generalise the type of this Id
405
406   deriving ( Eq )
407 \end{code}
408
409 For TyGenUInfo, the list has one entry for each usage annotation on
410 the type of the Id, in left-to-right pre-order (annotations come
411 before the type they annotate).  Nothing means no restriction; Just
412 usOnce or Just usMany forces that annotation to that value.  Other
413 usage annotations are illegal.
414
415 \begin{code}
416 seqTyGenInfo :: TyGenInfo -> ()
417 seqTyGenInfo  NoTyGenInfo    = ()
418 seqTyGenInfo (TyGenUInfo us) = seqList us ()
419 seqTyGenInfo  TyGenNever     = ()
420
421 noTyGenInfo :: TyGenInfo
422 noTyGenInfo = NoTyGenInfo
423
424 isNoTyGenInfo :: TyGenInfo -> Bool
425 isNoTyGenInfo NoTyGenInfo = True
426 isNoTyGenInfo _           = False
427
428 -- NB: There's probably no need to write this information out to the interface file.
429 -- Why?  Simply because imported identifiers never get their types re-inferred.
430 -- But it's definitely nice to see in dumps, it for debugging purposes.
431
432 ppTyGenInfo :: TyGenInfo -> SDoc
433 ppTyGenInfo  NoTyGenInfo    = empty
434 ppTyGenInfo (TyGenUInfo us) = ptext SLIT("__G") <+> text (tyGenInfoString us)
435 ppTyGenInfo  TyGenNever     = ptext SLIT("__G N")
436
437 tyGenInfoString us = map go us
438   where go  Nothing               = 'x'  -- for legibility, choose
439         go (Just u) | u == usOnce = '1'  -- chars with identity
440                     | u == usMany = 'M'  -- Z-encoding.
441         go other = pprPanic "IdInfo.tyGenInfoString: unexpected annotation" (ppr other)
442
443 instance Outputable TyGenInfo where
444   ppr = ppTyGenInfo
445
446 instance Show TyGenInfo where
447   showsPrec p c = showsPrecSDoc p (ppr c)
448 \end{code}
449
450
451 %************************************************************************
452 %*                                                                      *
453 \subsection[worker-IdInfo]{Worker info about an @Id@}
454 %*                                                                      *
455 %************************************************************************
456
457 If this Id has a worker then we store a reference to it. Worker
458 functions are generated by the worker/wrapper pass.  This uses
459 information from the strictness and CPR analyses.
460
461 There might not be a worker, even for a strict function, because:
462 (a) the function might be small enough to inline, so no need 
463     for w/w split
464 (b) the strictness info might be "SSS" or something, so no w/w split.
465
466 \begin{code}
467
468 data WorkerInfo = NoWorker
469                 | HasWorker Id Arity
470         -- The Arity is the arity of the *wrapper* at the moment of the
471         -- w/w split. See comments in MkIface.ifaceId, with the 'Worker' code.
472
473 seqWorker :: WorkerInfo -> ()
474 seqWorker (HasWorker id _) = id `seq` ()
475 seqWorker NoWorker         = ()
476
477 ppWorkerInfo NoWorker            = empty
478 ppWorkerInfo (HasWorker wk_id _) = ptext SLIT("__P") <+> ppr wk_id
479
480 noWorkerInfo = NoWorker
481
482 workerExists :: WorkerInfo -> Bool
483 workerExists NoWorker        = False
484 workerExists (HasWorker _ _) = True
485
486 workerId :: WorkerInfo -> Id
487 workerId (HasWorker id _) = id
488
489 wrapperArity :: WorkerInfo -> Arity
490 wrapperArity (HasWorker _ a) = a
491 \end{code}
492
493
494 %************************************************************************
495 %*                                                                      *
496 \subsection[CAF-IdInfo]{CAF-related information}
497 %*                                                                      *
498 %************************************************************************
499
500 This information is used to build Static Reference Tables (see
501 simplStg/ComputeSRT.lhs).
502
503 \begin{code}
504 data CafInfo 
505         = MayHaveCafRefs                -- either:
506                                         -- (1) A function or static constructor
507                                         --     that refers to one or more CAFs,
508                                         -- (2) A real live CAF
509
510         | NoCafRefs                     -- A function or static constructor
511                                         -- that refers to no CAFs.
512
513 -- LATER: not sure how easy this is...
514 --      | OneCafRef Id
515
516
517 seqCaf c = c `seq` ()
518
519 ppCafInfo NoCafRefs = ptext SLIT("__C")
520 ppCafInfo MayHaveCafRefs = empty
521 \end{code}
522
523
524 %************************************************************************
525 %*                                                                      *
526 \subsection[cpr-IdInfo]{Constructed Product Result info about an @Id@}
527 %*                                                                      *
528 %************************************************************************
529
530 If the @Id@ is a function then it may have CPR info. A CPR analysis
531 phase detects whether:
532
533 \begin{enumerate}
534 \item
535 The function's return value has a product type, i.e. an algebraic  type 
536 with a single constructor. Examples of such types are tuples and boxed
537 primitive values.
538 \item
539 The function always 'constructs' the value that it is returning.  It
540 must do this on every path through,  and it's OK if it calls another
541 function which constructs the result.
542 \end{enumerate}
543
544 If this is the case then we store a template which tells us the
545 function has the CPR property and which components of the result are
546 also CPRs.   
547
548 \begin{code}
549 data CprInfo
550   = NoCPRInfo
551   | ReturnsCPR  -- Yes, this function returns a constructed product
552                 -- Implicitly, this means "after the function has been applied
553                 -- to all its arguments", so the worker/wrapper builder in 
554                 -- WwLib.mkWWcpr checks that that it is indeed saturated before
555                 -- making use of the CPR info
556
557         -- We used to keep nested info about sub-components, but
558         -- we never used it so I threw it away
559 \end{code}
560
561 \begin{code}
562 seqCpr :: CprInfo -> ()
563 seqCpr ReturnsCPR = ()
564 seqCpr NoCPRInfo  = ()
565
566 noCprInfo       = NoCPRInfo
567
568 ppCprInfo NoCPRInfo  = empty
569 ppCprInfo ReturnsCPR = ptext SLIT("__M")
570
571 instance Outputable CprInfo where
572     ppr = ppCprInfo
573
574 instance Show CprInfo where
575     showsPrec p c = showsPrecSDoc p (ppr c)
576 \end{code}
577
578
579 %************************************************************************
580 %*                                                                      *
581 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
582 %*                                                                      *
583 %************************************************************************
584
585 If the @Id@ is a lambda-bound variable then it may have lambda-bound
586 var info.  The usage analysis (UsageSP) detects whether the lambda
587 binding this var is a ``one-shot'' lambda; that is, whether it is
588 applied at most once.
589
590 This information may be useful in optimisation, as computations may
591 safely be floated inside such a lambda without risk of duplicating
592 work.
593
594 \begin{code}
595 data LBVarInfo
596   = NoLBVarInfo
597
598   | LBVarInfo Type              -- The lambda that binds this Id has this usage
599                                 --   annotation (i.e., if ==usOnce, then the
600                                 --   lambda is applied at most once).
601                                 -- The annotation's kind must be `$'
602                                 -- HACK ALERT! placing this info here is a short-term hack,
603                                 --   but it minimises changes to the rest of the compiler.
604                                 --   Hack agreed by SLPJ/KSW 1999-04.
605
606 seqLBVar l = l `seq` ()
607 \end{code}
608
609 \begin{code}
610 noLBVarInfo = NoLBVarInfo
611
612 -- not safe to print or parse LBVarInfo because it is not really a
613 -- property of the definition, but a property of the context.
614 pprLBVarInfo NoLBVarInfo     = empty
615 pprLBVarInfo (LBVarInfo u)   | u == usOnce
616                              = getPprStyle $ \ sty ->
617                                if ifaceStyle sty
618                                then empty
619                                else ptext SLIT("OneShot")
620                              | otherwise
621                              = empty
622
623 instance Outputable LBVarInfo where
624     ppr = pprLBVarInfo
625
626 instance Show LBVarInfo where
627     showsPrec p c = showsPrecSDoc p (ppr c)
628 \end{code}
629
630
631 %************************************************************************
632 %*                                                                      *
633 \subsection{Bulk operations on IdInfo}
634 %*                                                                      *
635 %************************************************************************
636
637 zapFragileInfo is used when cloning binders, mainly in the
638 simplifier.  We must forget about used-once information because that
639 isn't necessarily correct in the transformed program.
640 Also forget specialisations and unfoldings because they would need
641 substitution to be correct.  (They get pinned back on separately.)
642
643 \begin{code}
644 zapFragileInfo :: IdInfo -> Maybe IdInfo
645 zapFragileInfo info@(IdInfo {occInfo            = occ, 
646                              workerInfo         = wrkr,
647                              specInfo           = rules, 
648                              unfoldingInfo      = unfolding})
649   |  not (isFragileOcc occ)
650         -- We must forget about whether it was marked safe-to-inline,
651         -- because that isn't necessarily true in the simplified expression.
652         -- This is important because expressions may  be re-simplified
653         -- We don't zap deadness or loop-breaker-ness.
654         -- The latter is important because it tells MkIface not to 
655         -- spit out an inlining for the thing.  The former doesn't
656         -- seem so important, but there's no harm.
657
658   && isEmptyCoreRules rules
659         -- Specialisations would need substituting.  They get pinned
660         -- back on separately.
661
662   && not (workerExists wrkr)
663
664   && not (hasUnfolding unfolding)
665         -- This is very important; occasionally a let-bound binder is used
666         -- as a binder in some lambda, in which case its unfolding is utterly
667         -- bogus.  Also the unfolding uses old binders so if we left it we'd
668         -- have to substitute it. Much better simply to give the Id a new
669         -- unfolding each time, which is what the simplifier does.
670   = Nothing
671
672   | otherwise
673   = Just (info {occInfo         = robust_occ_info,
674                 workerInfo      = noWorkerInfo,
675                 specInfo        = emptyCoreRules,
676                 unfoldingInfo   = noUnfolding})
677   where
678         -- It's important to keep the loop-breaker info,
679         -- because the substitution doesn't remember it.
680     robust_occ_info = case occ of
681                         OneOcc _ _ -> NoOccInfo
682                         other      -> occ
683 \end{code}
684
685 @zapLamInfo@ is used for lambda binders that turn out to to be
686 part of an unsaturated lambda
687
688 \begin{code}
689 zapLamInfo :: IdInfo -> Maybe IdInfo
690 zapLamInfo info@(IdInfo {occInfo = occ, demandInfo = demand})
691   | is_safe_occ && not (isStrict demand)
692   = Nothing
693   | otherwise
694   = Just (info {occInfo = safe_occ,
695                 demandInfo = wwLazy})
696   where
697         -- The "unsafe" occ info is the ones that say I'm not in a lambda
698         -- because that might not be true for an unsaturated lambda
699     is_safe_occ = case occ of
700                         OneOcc in_lam once -> in_lam
701                         other              -> True
702
703     safe_occ = case occ of
704                  OneOcc _ once -> OneOcc insideLam once
705                  other         -> occ
706 \end{code}
707
708
709 copyIdInfo is used when shorting out a top-level binding
710         f_local = BIG
711         f = f_local
712 where f is exported.  We are going to swizzle it around to
713         f = BIG
714         f_local = f
715
716 BUT (a) we must be careful about messing up rules
717     (b) we must ensure f's IdInfo ends up right
718
719 (a) Messing up the rules
720 ~~~~~~~~~~~~~~~~~~~~
721 The example that went bad on me was this one:
722         
723     iterate :: (a -> a) -> a -> [a]
724     iterate = iterateList
725     
726     iterateFB c f x = x `c` iterateFB c f (f x)
727     iterateList f x =  x : iterateList f (f x)
728     
729     {-# RULES
730     "iterate"   forall f x.     iterate f x = build (\c _n -> iterateFB c f x)
731     "iterateFB"                 iterateFB (:) = iterateList
732      #-}
733
734 This got shorted out to:
735
736     iterateList :: (a -> a) -> a -> [a]
737     iterateList = iterate
738     
739     iterateFB c f x = x `c` iterateFB c f (f x)
740     iterate f x =  x : iterate f (f x)
741     
742     {-# RULES
743     "iterate"   forall f x.     iterate f x = build (\c _n -> iterateFB c f x)
744     "iterateFB"                 iterateFB (:) = iterate
745      #-}
746
747 And now we get an infinite loop in the rule system 
748         iterate f x -> build (\cn -> iterateFB c f x
749                     -> iterateFB (:) f x
750                     -> iterate f x
751
752 Tiresome solution: don't do shorting out if f has rewrite rules.
753 Hence shortableIdInfo.
754
755 (b) Keeping the IdInfo right
756 ~~~~~~~~~~~~~~~~~~~~~~~~
757 We want to move strictness/worker info from f_local to f, but keep the rest.
758 Hence copyIdInfo.
759
760 \begin{code}
761 shortableIdInfo :: IdInfo -> Bool
762 shortableIdInfo info = isEmptyCoreRules (specInfo info)
763
764 copyIdInfo :: IdInfo    -- f_local
765            -> IdInfo    -- f (the exported one)
766            -> IdInfo    -- New info for f
767 copyIdInfo f_local f = f { strictnessInfo = strictnessInfo f_local,
768                            workerInfo     = workerInfo     f_local,
769                            cprInfo        = cprInfo        f_local
770                           }
771 \end{code}