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