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