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