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