2c36363b4e0de97ad9b4c1c10a903a3b3b87abd3
[ghc-hetmet.git] / ghc / compiler / basicTypes / IdInfo.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
3 %
4 \section[IdInfo]{@IdInfos@: Non-essential information about @Ids@}
5
6 (And a pretty good illustration of quite a few things wrong with
7 Haskell. [WDP 94/11])
8
9 \begin{code}
10 module IdInfo (
11         IdInfo,         -- Abstract
12
13         vanillaIdInfo, mkIdInfo,
14
15         -- Flavour
16         IdFlavour(..), flavourInfo, 
17         setNoDiscardInfo, zapSpecPragInfo, copyIdInfo,
18         ppFlavourInfo,
19
20         -- Arity
21         ArityInfo(..),
22         exactArity, atLeastArity, unknownArity, hasArity,
23         arityInfo, setArityInfo, ppArityInfo, arityLowerBound,
24
25         -- Strictness
26         StrictnessInfo(..),                             -- Non-abstract
27         mkStrictnessInfo,
28         noStrictnessInfo, strictnessInfo,
29         ppStrictnessInfo, setStrictnessInfo, 
30         isBottomingStrictness, appIsBottom,
31
32         -- Worker
33         WorkerInfo, workerExists, 
34         workerInfo, setWorkerInfo, ppWorkerInfo,
35
36         -- Unfolding
37         unfoldingInfo, setUnfoldingInfo, 
38
39         -- DemandInfo
40         demandInfo, setDemandInfo, 
41
42         -- Inline prags
43         InlinePragInfo(..), OccInfo(..),
44         inlinePragInfo, setInlinePragInfo, notInsideLambda,
45
46         -- Specialisation
47         specInfo, setSpecInfo,
48
49         -- Update
50         UpdateInfo, UpdateSpec,
51         mkUpdateInfo, updateInfo, updateInfoMaybe, ppUpdateInfo, setUpdateInfo,
52
53         -- CAF info
54         CafInfo(..), cafInfo, setCafInfo, ppCafInfo,
55
56         -- Constructed Product Result Info
57         CprInfo(..), cprInfo, setCprInfo, ppCprInfo, noCprInfo,
58
59         -- Zapping
60         zapLamIdInfo, zapFragileIdInfo,
61
62         -- Lambda-bound variable info
63         LBVarInfo(..), lbvarInfo, setLBVarInfo, noLBVarInfo
64     ) where
65
66 #include "HsVersions.h"
67
68
69 import {-# SOURCE #-} CoreUnfold ( Unfolding, noUnfolding, hasUnfolding )
70 import {-# SOURCE #-} CoreSyn    ( CoreExpr, CoreRules, emptyCoreRules, isEmptyCoreRules )
71 import {-# SOURCE #-} Const      ( Con )
72
73 import Var              ( Id )
74 import FieldLabel       ( FieldLabel )
75 import Demand           ( Demand, isStrict, isLazy, wwLazy, pprDemands )
76 import Type             ( UsageAnn )
77 import Outputable       
78 import Maybe            ( isJust )
79
80 infixl  1 `setUpdateInfo`,
81           `setDemandInfo`,
82           `setStrictnessInfo`,
83           `setSpecInfo`,
84           `setArityInfo`,
85           `setInlinePragInfo`,
86           `setUnfoldingInfo`,
87           `setCprInfo`,
88           `setWorkerInfo`,
89           `setCafInfo`
90         -- infixl so you can say (id `set` a `set` b)
91 \end{code}
92
93 An @IdInfo@ gives {\em optional} information about an @Id@.  If
94 present it never lies, but it may not be present, in which case there
95 is always a conservative assumption which can be made.
96
97         There is one exception: the 'flavour' is *not* optional.
98         You must not discard it.
99         It used to be in Var.lhs, but that seems unclean.
100
101 Two @Id@s may have different info even though they have the same
102 @Unique@ (and are hence the same @Id@); for example, one might lack
103 the properties attached to the other.
104
105 The @IdInfo@ gives information about the value, or definition, of the
106 @Id@.  It does {\em not} contain information about the @Id@'s usage
107 (except for @DemandInfo@? ToDo). (@lbvarInfo@ is also a marginal
108 case.  KSW 1999-04).
109
110 \begin{code}
111 data IdInfo
112   = IdInfo {
113         flavourInfo     :: IdFlavour,           -- NOT OPTIONAL
114         arityInfo       :: ArityInfo,           -- Its arity
115         demandInfo      :: Demand,              -- Whether or not it is definitely demanded
116         specInfo        :: CoreRules,           -- Specialisations of this function which exist
117         strictnessInfo  :: StrictnessInfo,      -- Strictness properties
118         workerInfo      :: WorkerInfo,          -- Pointer to Worker Function
119         unfoldingInfo   :: Unfolding,           -- Its unfolding
120         updateInfo      :: UpdateInfo,          -- Which args should be updated
121         cafInfo         :: CafInfo,
122         cprInfo         :: CprInfo,             -- Function always constructs a product result
123         lbvarInfo       :: LBVarInfo,           -- Info about a lambda-bound variable
124         inlinePragInfo  :: !InlinePragInfo      -- Inline pragmas
125     }
126 \end{code}
127
128 Setters
129
130 \begin{code}
131 setUpdateInfo     info ud = info { updateInfo = ud }
132 setDemandInfo     info dd = info { demandInfo = dd }
133 setStrictnessInfo info st = info { strictnessInfo = st }
134 setWorkerInfo     info wk = info { workerInfo = wk }
135 setSpecInfo       info sp = info { specInfo = sp }
136 setArityInfo      info ar = info { arityInfo = ar  }
137 setInlinePragInfo info pr = info { inlinePragInfo = pr }
138 setUnfoldingInfo  info uf = info { unfoldingInfo = uf }
139 setCafInfo        info cf = info { cafInfo = cf }
140 setCprInfo        info cp = info { cprInfo = cp }
141 setLBVarInfo      info lb = info { lbvarInfo = lb }
142
143 setNoDiscardInfo  info = case flavourInfo info of
144                                 VanillaId -> info { flavourInfo = NoDiscardId }
145                                 other     -> info
146 zapSpecPragInfo   info = case flavourInfo info of
147                                 SpecPragmaId -> info { flavourInfo = VanillaId }
148                                 other        -> info
149
150 copyIdInfo :: IdInfo    -- From
151            -> IdInfo    -- To
152            -> IdInfo    -- To updated with stuff from From; except flavour unchanged
153 -- copyIdInfo is used when shorting out a top-level binding
154 --      f_local = BIG
155 --      f = f_local
156 -- where f is exported.  We are going to swizzle it around to
157 --      f = BIG
158 --      f_local = f
159 -- but we must be careful to combine their IdInfos right.
160 -- The fact that things can go wrong here is a bad sign, but I can't see
161 -- how to make it 'patently right', so copyIdInfo is derived (pretty much) by trial and error
162 --
163 -- Here 'from' is f_local, 'to' is f.
164
165 copyIdInfo from to = from { flavourInfo = flavourInfo to,
166                             specInfo = specInfo to
167                           }
168         -- It's important to propagate the inline pragmas from bndr
169         -- to exportd_id.  Ditto strictness etc.  This "bites" when we use an INLNE pragma:
170         --      {-# INLINE f #-}
171         --      f x = (x,x)
172         --
173         -- This becomes (where the "*" means INLINE prag)
174         --
175         --      M.f = /\a -> let mf* = \x -> (x,x) in mf
176         --
177         -- Now the mf floats out and we end up with the trivial binding
178         --
179         --      mf* = /\a -> \x -> (x,x)
180         --      M.f = mf
181         --
182         -- Now, when we short out the M.f = mf binding we must preserve the inline
183         -- pragma on the mf binding.
184         --
185         -- On the other hand, transformation rules may be attached to the 
186         -- 'to' Id, and we want to preserve them.  
187 \end{code}
188
189
190 \begin{code}
191 vanillaIdInfo :: IdInfo
192 vanillaIdInfo = mkIdInfo VanillaId
193
194 mkIdInfo :: IdFlavour -> IdInfo
195 mkIdInfo flv = IdInfo {
196                     flavourInfo         = flv,
197                     arityInfo           = UnknownArity,
198                     demandInfo          = wwLazy,
199                     specInfo            = emptyCoreRules,
200                     workerInfo          = Nothing,
201                     strictnessInfo      = NoStrictnessInfo,
202                     unfoldingInfo       = noUnfolding,
203                     updateInfo          = NoUpdateInfo,
204                     cafInfo             = MayHaveCafRefs,
205                     cprInfo             = NoCPRInfo,
206                     lbvarInfo           = NoLBVarInfo,
207                     inlinePragInfo      = NoInlinePragInfo
208            }
209 \end{code}
210
211
212 %************************************************************************
213 %*                                                                      *
214 \subsection{Flavour}
215 %*                                                                      *
216 %************************************************************************
217
218 \begin{code}
219 data IdFlavour
220   = VanillaId                           -- Most Ids are like this
221   | ConstantId Con                      -- The Id for a constant (data constructor or primop)
222   | RecordSelId FieldLabel              -- The Id for a record selector
223   | SpecPragmaId                        -- Don't discard these
224   | NoDiscardId                         -- Don't discard these either
225
226 ppFlavourInfo :: IdFlavour -> SDoc
227 ppFlavourInfo VanillaId       = empty
228 ppFlavourInfo (ConstantId _)  = ptext SLIT("[Constr]")
229 ppFlavourInfo (RecordSelId _) = ptext SLIT("[RecSel]")
230 ppFlavourInfo SpecPragmaId    = ptext SLIT("[SpecPrag]")
231 ppFlavourInfo NoDiscardId     = ptext SLIT("[NoDiscard]")
232 \end{code}
233
234 The @SpecPragmaId@ exists only to make Ids that are
235 on the *LHS* of bindings created by SPECIALISE pragmas; 
236 eg:             s = f Int d
237 The SpecPragmaId is never itself mentioned; it
238 exists solely so that the specialiser will find
239 the call to f, and make specialised version of it.
240 The SpecPragmaId binding is discarded by the specialiser
241 when it gathers up overloaded calls.
242 Meanwhile, it is not discarded as dead code.
243
244
245 %************************************************************************
246 %*                                                                      *
247 \subsection[arity-IdInfo]{Arity info about an @Id@}
248 %*                                                                      *
249 %************************************************************************
250
251 For locally-defined Ids, the code generator maintains its own notion
252 of their arities; so it should not be asking...  (but other things
253 besides the code-generator need arity info!)
254
255 \begin{code}
256 data ArityInfo
257   = UnknownArity        -- No idea
258   | ArityExactly Int    -- Arity is exactly this
259   | ArityAtLeast Int    -- Arity is this or greater
260
261 exactArity   = ArityExactly
262 atLeastArity = ArityAtLeast
263 unknownArity = UnknownArity
264
265 arityLowerBound :: ArityInfo -> Int
266 arityLowerBound UnknownArity     = 0
267 arityLowerBound (ArityAtLeast n) = n
268 arityLowerBound (ArityExactly n) = n
269
270 hasArity :: ArityInfo -> Bool
271 hasArity UnknownArity = False
272 hasArity other        = True
273
274 ppArityInfo UnknownArity         = empty
275 ppArityInfo (ArityExactly arity) = hsep [ptext SLIT("__A"), int arity]
276 ppArityInfo (ArityAtLeast arity) = hsep [ptext SLIT("__AL"), int arity]
277 \end{code}
278
279 %************************************************************************
280 %*                                                                      *
281 \subsection{Inline-pragma information}
282 %*                                                                      *
283 %************************************************************************
284
285 \begin{code}
286 data InlinePragInfo
287   = NoInlinePragInfo
288
289   | IMustNotBeINLINEd   -- User NOINLINE pragma
290
291   | IAmALoopBreaker     -- Used by the occurrence analyser to mark loop-breakers
292                         -- in a group of recursive definitions
293
294   | ICanSafelyBeINLINEd -- Used by the occurrence analyser to mark things
295                         -- that manifesly occur once, not inside SCCs, 
296                         -- not in constructor arguments
297
298         OccInfo         -- Says whether the occurrence is inside a lambda
299                         --      If so, must only substitute WHNFs
300
301         Bool            -- False <=> occurs in more than one case branch
302                         --      If so, there's a code-duplication issue
303
304   | IAmDead             -- Marks unused variables.  Sometimes useful for
305                         -- lambda and case-bound variables.
306
307   | IMustBeINLINEd      -- Absolutely must inline; used for PrimOps and
308                         -- constructors only.
309
310 instance Outputable InlinePragInfo where
311   ppr NoInlinePragInfo          = empty
312   ppr IMustBeINLINEd            = ptext SLIT("__UU")
313   ppr IMustNotBeINLINEd         = ptext SLIT("__Unot")
314   ppr IAmALoopBreaker           = ptext SLIT("__Ux")
315   ppr IAmDead                   = ptext SLIT("__Ud")
316   ppr (ICanSafelyBeINLINEd InsideLam _) = ptext SLIT("__Ul")
317   ppr (ICanSafelyBeINLINEd _ _) = ptext SLIT("__Us")
318
319 instance Show InlinePragInfo where
320   showsPrec p prag = showsPrecSDoc p (ppr prag)
321 \end{code}
322
323 \begin{code}
324 data OccInfo
325   = NotInsideLam
326
327   | InsideLam           -- Inside a non-linear lambda (that is, a lambda which
328                         -- is sure to be instantiated only once).
329                         -- Substituting a redex for this occurrence is
330                         -- dangerous because it might duplicate work.
331
332 instance Outputable OccInfo where
333   ppr NotInsideLam = empty
334   ppr InsideLam    = text "l"
335
336
337 notInsideLambda :: OccInfo -> Bool
338 notInsideLambda NotInsideLam = True
339 notInsideLambda InsideLam    = False
340 \end{code}
341
342 %************************************************************************
343 %*                                                                      *
344 \subsection[strictness-IdInfo]{Strictness info about an @Id@}
345 %*                                                                      *
346 %************************************************************************
347
348 We specify the strictness of a function by giving information about
349 each of the ``wrapper's'' arguments (see the description about
350 worker/wrapper-style transformations in the PJ/Launchbury paper on
351 unboxed types).
352
353 The list of @Demands@ specifies: (a)~the strictness properties of a
354 function's arguments; and (b)~the type signature of that worker (if it
355 exists); i.e. its calling convention.
356
357 Note that the existence of a worker function is now denoted by the Id's
358 workerInfo field.
359
360 \begin{code}
361 data StrictnessInfo
362   = NoStrictnessInfo
363
364   | StrictnessInfo [Demand] 
365                    Bool         -- True <=> the function diverges regardless of its arguments
366                                 -- Useful for "error" and other disguised variants thereof.  
367                                 -- BUT NB: f = \x y. error "urk"
368                                 --         will have info  SI [SS] True
369                                 -- but still (f) and (f 2) are not bot; only (f 3 2) is bot
370 \end{code}
371
372 \begin{code}
373 mkStrictnessInfo :: ([Demand], Bool) -> StrictnessInfo
374
375 mkStrictnessInfo (xs, is_bot)
376   | all isLazy xs && not is_bot = NoStrictnessInfo              -- Uninteresting
377   | otherwise                   = StrictnessInfo xs is_bot
378
379 noStrictnessInfo       = NoStrictnessInfo
380
381 isBottomingStrictness (StrictnessInfo _ bot) = bot
382 isBottomingStrictness NoStrictnessInfo       = False
383
384 -- appIsBottom returns true if an application to n args would diverge
385 appIsBottom (StrictnessInfo ds bot)   n = bot && (n >= length ds)
386 appIsBottom  NoStrictnessInfo         n = False
387
388 ppStrictnessInfo NoStrictnessInfo = empty
389 ppStrictnessInfo (StrictnessInfo wrapper_args bot)
390   = hsep [ptext SLIT("__S"), pprDemands wrapper_args bot]
391 \end{code}
392
393 %************************************************************************
394 %*                                                                      *
395 \subsection[worker-IdInfo]{Worker info about an @Id@}
396 %*                                                                      *
397 %************************************************************************
398
399 If this Id has a worker then we store a reference to it. Worker
400 functions are generated by the worker/wrapper pass.  This uses
401 information from the strictness and CPR analyses.
402
403 There might not be a worker, even for a strict function, because:
404 (a) the function might be small enough to inline, so no need 
405     for w/w split
406 (b) the strictness info might be "SSS" or something, so no w/w split.
407
408 \begin{code}
409
410 type WorkerInfo = Maybe Id
411
412 {- UNUSED:
413 mkWorkerInfo :: Id -> WorkerInfo
414 mkWorkerInfo wk_id = Just wk_id
415 -}
416
417 ppWorkerInfo Nothing      = empty
418 ppWorkerInfo (Just wk_id) = ptext SLIT("__P") <+> ppr wk_id
419
420 noWorkerInfo = Nothing
421
422 workerExists :: Maybe Id -> Bool
423 workerExists = isJust
424 \end{code}
425
426
427 %************************************************************************
428 %*                                                                      *
429 \subsection[update-IdInfo]{Update-analysis info about an @Id@}
430 %*                                                                      *
431 %************************************************************************
432
433 \begin{code}
434 data UpdateInfo
435   = NoUpdateInfo
436   | SomeUpdateInfo UpdateSpec
437   deriving (Eq, Ord)
438       -- we need Eq/Ord to cross-chk update infos in interfaces
439
440 -- the form in which we pass update-analysis info between modules:
441 type UpdateSpec = [Int]
442 \end{code}
443
444 \begin{code}
445 mkUpdateInfo = SomeUpdateInfo
446
447 updateInfoMaybe NoUpdateInfo        = Nothing
448 updateInfoMaybe (SomeUpdateInfo []) = Nothing
449 updateInfoMaybe (SomeUpdateInfo  u) = Just u
450 \end{code}
451
452 Text instance so that the update annotations can be read in.
453
454 \begin{code}
455 ppUpdateInfo NoUpdateInfo          = empty
456 ppUpdateInfo (SomeUpdateInfo [])   = empty
457 ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("__U ")) (hcat (map int spec))
458 \end{code}
459
460 %************************************************************************
461 %*                                                                      *
462 \subsection[CAF-IdInfo]{CAF-related information}
463 %*                                                                      *
464 %************************************************************************
465
466 This information is used to build Static Reference Tables (see
467 simplStg/ComputeSRT.lhs).
468
469 \begin{code}
470 data CafInfo 
471         = MayHaveCafRefs                -- either:
472                                         -- (1) A function or static constructor
473                                         --     that refers to one or more CAFs,
474                                         -- (2) A real live CAF
475
476         | NoCafRefs                     -- A function or static constructor
477                                         -- that refers to no CAFs.
478
479 -- LATER: not sure how easy this is...
480 --      | OneCafRef Id
481
482
483 ppCafInfo NoCafRefs = ptext SLIT("__C")
484 ppCafInfo MayHaveCafRefs = empty
485 \end{code}
486
487
488 %************************************************************************
489 %*                                                                      *
490 \subsection[CAF-IdInfo]{CAF-related information}
491 %*                                                                      *
492 %************************************************************************
493
494 zapFragileIdInfo is used when cloning binders, mainly in the
495 simplifier.  We must forget about used-once information because that
496 isn't necessarily correct in the transformed program.
497 Also forget specialisations and unfoldings because they would need
498 substitution to be correct.  (They get pinned back on separately.)
499
500 \begin{code}
501 zapFragileIdInfo :: IdInfo -> Maybe IdInfo
502 zapFragileIdInfo info@(IdInfo {inlinePragInfo   = inline_prag, 
503                                workerInfo       = wrkr,
504                                specInfo         = rules, 
505                                unfoldingInfo    = unfolding})
506   |  not is_fragile_inline_prag 
507         -- We must forget about whether it was marked safe-to-inline,
508         -- because that isn't necessarily true in the simplified expression.
509         -- This is important because expressions may  be re-simplified
510
511   && isEmptyCoreRules rules
512         -- Specialisations would need substituting.  They get pinned
513         -- back on separately.
514
515   && not (workerExists wrkr)
516
517   && not (hasUnfolding unfolding)
518         -- This is very important; occasionally a let-bound binder is used
519         -- as a binder in some lambda, in which case its unfolding is utterly
520         -- bogus.  Also the unfolding uses old binders so if we left it we'd
521         -- have to substitute it. Much better simply to give the Id a new
522         -- unfolding each time, which is what the simplifier does.
523   = Nothing
524
525   | otherwise
526   = Just (info {inlinePragInfo  = safe_inline_prag, 
527                 workerInfo      = noWorkerInfo,
528                 specInfo        = emptyCoreRules,
529                 unfoldingInfo   = noUnfolding})
530
531   where
532     is_fragile_inline_prag = case inline_prag of
533                                 ICanSafelyBeINLINEd _ _ -> True
534
535 -- We used to say the dead-ness was fragile, but I don't
536 -- see why it is.  Furthermore, deadness is a pain to lose;
537 -- see Simplify.mkDupableCont (Select ...)
538 --                              IAmDead                 -> True
539
540                                 other                   -> False
541
542         -- Be careful not to destroy real 'pragma' info
543     safe_inline_prag | is_fragile_inline_prag = NoInlinePragInfo
544                      | otherwise              = inline_prag
545 \end{code}
546
547
548 @zapLamIdInfo@ is used for lambda binders that turn out to to be
549 part of an unsaturated lambda
550
551 \begin{code}
552 zapLamIdInfo :: IdInfo -> Maybe IdInfo
553 zapLamIdInfo info@(IdInfo {inlinePragInfo = inline_prag, demandInfo = demand})
554   | is_safe_inline_prag && not (isStrict demand)
555   = Nothing
556   | otherwise
557   = Just (info {inlinePragInfo = safe_inline_prag,
558                 demandInfo = wwLazy})
559   where
560         -- The "unsafe" prags are the ones that say I'm not in a lambda
561         -- because that might not be true for an unsaturated lambda
562     is_safe_inline_prag = case inline_prag of
563                                 ICanSafelyBeINLINEd NotInsideLam nalts -> False
564                                 other                                  -> True
565
566     safe_inline_prag    = case inline_prag of
567                                 ICanSafelyBeINLINEd _ nalts
568                                       -> ICanSafelyBeINLINEd InsideLam nalts
569                                 other -> inline_prag
570 \end{code}
571
572
573 %************************************************************************
574 %*                                                                      *
575 \subsection[cpr-IdInfo]{Constructed Product Result info about an @Id@}
576 %*                                                                      *
577 %************************************************************************
578
579 If the @Id@ is a function then it may have CPR info. A CPR analysis
580 phase detects whether:
581
582 \begin{enumerate}
583 \item
584 The function's return value has a product type, i.e. an algebraic  type 
585 with a single constructor. Examples of such types are tuples and boxed
586 primitive values.
587 \item
588 The function always 'constructs' the value that it is returning.  It
589 must do this on every path through,  and it's OK if it calls another
590 function which constructs the result.
591 \end{enumerate}
592
593 If this is the case then we store a template which tells us the
594 function has the CPR property and which components of the result are
595 also CPRs.   
596
597 \begin{code}
598 data CprInfo
599   = NoCPRInfo
600
601   | CPRInfo [CprInfo] 
602
603 -- e.g. const 5 == CPRInfo [NoCPRInfo]
604 --              == __M(-)
605 --      \x -> (5,
606 --              (x,
607 --               5,
608 --               x)
609 --            ) 
610 --            CPRInfo [CPRInfo [NoCPRInfo], 
611 --                     CPRInfo [NoCprInfo,
612 --                              CPRInfo [NoCPRInfo],
613 --                              NoCPRInfo]
614 --                    ]
615 --            __M((-)(-(-)-)-)
616 \end{code}
617
618 \begin{code}
619
620 noCprInfo       = NoCPRInfo
621
622 ppCprInfo NoCPRInfo = empty
623 ppCprInfo c@(CPRInfo _)
624   = hsep [ptext SLIT("__M"), ppCprInfo' c]
625     where
626     ppCprInfo' NoCPRInfo      = char '-'
627     ppCprInfo' (CPRInfo args) = parens (hcat (map ppCprInfo' args))
628
629 instance Outputable CprInfo where
630     ppr = ppCprInfo
631
632 instance Show CprInfo where
633     showsPrec p c = showsPrecSDoc p (ppr c)
634 \end{code}
635
636
637 %************************************************************************
638 %*                                                                      *
639 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
640 %*                                                                      *
641 %************************************************************************
642
643 If the @Id@ is a lambda-bound variable then it may have lambda-bound
644 var info.  The usage analysis (UsageSP) detects whether the lambda
645 binding this var is a ``one-shot'' lambda; that is, whether it is
646 applied at most once.
647
648 This information may be useful in optimisation, as computations may
649 safely be floated inside such a lambda without risk of duplicating
650 work.
651
652 \begin{code}
653 data LBVarInfo
654   = NoLBVarInfo
655
656   | IsOneShotLambda             -- The lambda that binds this Id is applied
657                                 --   at most once
658                                 -- HACK ALERT! placing this info here is a short-term hack,
659                                 --   but it minimises changes to the rest of the compiler.
660                                 --   Hack agreed by SLPJ/KSW 1999-04.
661 \end{code}
662
663 \begin{code}
664 noLBVarInfo = NoLBVarInfo
665
666 -- not safe to print or parse LBVarInfo because it is not really a
667 -- property of the definition, but a property of the context.
668 pprLBVarInfo NoLBVarInfo     = empty
669 pprLBVarInfo IsOneShotLambda = getPprStyle $ \ sty ->
670                                if ifaceStyle sty then empty
671                                                  else ptext SLIT("OneShot")
672
673 instance Outputable LBVarInfo where
674     ppr = pprLBVarInfo
675
676 instance Show LBVarInfo where
677     showsPrec p c = showsPrecSDoc p (ppr c)
678 \end{code}