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