[project @ 1999-05-26 14:12:07 by simonmar]
[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,
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,
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
271 ppArityInfo UnknownArity         = empty
272 ppArityInfo (ArityExactly arity) = hsep [ptext SLIT("__A"), int arity]
273 ppArityInfo (ArityAtLeast arity) = hsep [ptext SLIT("__AL"), int arity]
274 \end{code}
275
276 %************************************************************************
277 %*                                                                      *
278 \subsection{Inline-pragma information}
279 %*                                                                      *
280 %************************************************************************
281
282 \begin{code}
283 data InlinePragInfo
284   = NoInlinePragInfo
285
286   | IMustNotBeINLINEd   -- User NOINLINE pragma
287
288   | IAmALoopBreaker     -- Used by the occurrence analyser to mark loop-breakers
289                         -- in a group of recursive definitions
290
291   | ICanSafelyBeINLINEd -- Used by the occurrence analyser to mark things
292                         -- that manifesly occur once, not inside SCCs, 
293                         -- not in constructor arguments
294
295         OccInfo         -- Says whether the occurrence is inside a lambda
296                         --      If so, must only substitute WHNFs
297
298         Bool            -- False <=> occurs in more than one case branch
299                         --      If so, there's a code-duplication issue
300
301   | IAmDead             -- Marks unused variables.  Sometimes useful for
302                         -- lambda and case-bound variables.
303
304   | IMustBeINLINEd      -- Absolutely must inline; used for PrimOps and
305                         -- constructors only.
306
307 instance Outputable InlinePragInfo where
308   ppr NoInlinePragInfo          = empty
309   ppr IMustBeINLINEd            = ptext SLIT("__UU")
310   ppr IMustNotBeINLINEd         = ptext SLIT("__Unot")
311   ppr IAmALoopBreaker           = ptext SLIT("__Ux")
312   ppr IAmDead                   = ptext SLIT("__Ud")
313   ppr (ICanSafelyBeINLINEd InsideLam _) = ptext SLIT("__Ul")
314   ppr (ICanSafelyBeINLINEd _ _) = ptext SLIT("__Us")
315
316 instance Show InlinePragInfo where
317   showsPrec p prag = showsPrecSDoc p (ppr prag)
318 \end{code}
319
320 \begin{code}
321 data OccInfo
322   = NotInsideLam
323
324   | InsideLam           -- Inside a non-linear lambda (that is, a lambda which
325                         -- is sure to be instantiated only once).
326                         -- Substituting a redex for this occurrence is
327                         -- dangerous because it might duplicate work.
328
329 instance Outputable OccInfo where
330   ppr NotInsideLam = empty
331   ppr InsideLam    = text "l"
332
333
334 notInsideLambda :: OccInfo -> Bool
335 notInsideLambda NotInsideLam = True
336 notInsideLambda InsideLam    = False
337 \end{code}
338
339 %************************************************************************
340 %*                                                                      *
341 \subsection[strictness-IdInfo]{Strictness info about an @Id@}
342 %*                                                                      *
343 %************************************************************************
344
345 We specify the strictness of a function by giving information about
346 each of the ``wrapper's'' arguments (see the description about
347 worker/wrapper-style transformations in the PJ/Launchbury paper on
348 unboxed types).
349
350 The list of @Demands@ specifies: (a)~the strictness properties of a
351 function's arguments; and (b)~the type signature of that worker (if it
352 exists); i.e. its calling convention.
353
354 Note that the existence of a worker function is now denoted by the Id's
355 workerInfo field.
356
357 \begin{code}
358 data StrictnessInfo
359   = NoStrictnessInfo
360
361   | StrictnessInfo [Demand] 
362                    Bool         -- True <=> the function diverges regardless of its arguments
363                                 -- Useful for "error" and other disguised variants thereof.  
364                                 -- BUT NB: f = \x y. error "urk"
365                                 --         will have info  SI [SS] True
366                                 -- but still (f) and (f 2) are not bot; only (f 3 2) is bot
367 \end{code}
368
369 \begin{code}
370 mkStrictnessInfo :: ([Demand], Bool) -> StrictnessInfo
371
372 mkStrictnessInfo (xs, is_bot)
373   | all isLazy xs && not is_bot = NoStrictnessInfo              -- Uninteresting
374   | otherwise                   = StrictnessInfo xs is_bot
375
376 noStrictnessInfo       = NoStrictnessInfo
377
378 isBottomingStrictness (StrictnessInfo _ bot) = bot
379 isBottomingStrictness NoStrictnessInfo       = False
380
381 -- appIsBottom returns true if an application to n args would diverge
382 appIsBottom (StrictnessInfo ds bot)   n = bot && (n >= length ds)
383 appIsBottom  NoStrictnessInfo         n = False
384
385 ppStrictnessInfo NoStrictnessInfo = empty
386 ppStrictnessInfo (StrictnessInfo wrapper_args bot)
387   = hsep [ptext SLIT("__S"), pprDemands wrapper_args bot]
388 \end{code}
389
390 %************************************************************************
391 %*                                                                      *
392 \subsection[worker-IdInfo]{Worker info about an @Id@}
393 %*                                                                      *
394 %************************************************************************
395
396 If this Id has a worker then we store a reference to it. Worker
397 functions are generated by the worker/wrapper pass.  This uses
398 information from the strictness and CPR analyses.
399
400 There might not be a worker, even for a strict function, because:
401 (a) the function might be small enough to inline, so no need 
402     for w/w split
403 (b) the strictness info might be "SSS" or something, so no w/w split.
404
405 \begin{code}
406
407 type WorkerInfo = Maybe Id
408
409 {- UNUSED:
410 mkWorkerInfo :: Id -> WorkerInfo
411 mkWorkerInfo wk_id = Just wk_id
412
413 ppWorkerInfo Nothing      = empty
414 ppWorkerInfo (Just wk_id) = ppr wk_id
415 -}
416
417 noWorkerInfo = Nothing
418
419 workerExists :: Maybe Id -> Bool
420 workerExists = isJust
421 \end{code}
422
423
424 %************************************************************************
425 %*                                                                      *
426 \subsection[update-IdInfo]{Update-analysis info about an @Id@}
427 %*                                                                      *
428 %************************************************************************
429
430 \begin{code}
431 data UpdateInfo
432   = NoUpdateInfo
433   | SomeUpdateInfo UpdateSpec
434   deriving (Eq, Ord)
435       -- we need Eq/Ord to cross-chk update infos in interfaces
436
437 -- the form in which we pass update-analysis info between modules:
438 type UpdateSpec = [Int]
439 \end{code}
440
441 \begin{code}
442 mkUpdateInfo = SomeUpdateInfo
443
444 updateInfoMaybe NoUpdateInfo        = Nothing
445 updateInfoMaybe (SomeUpdateInfo []) = Nothing
446 updateInfoMaybe (SomeUpdateInfo  u) = Just u
447 \end{code}
448
449 Text instance so that the update annotations can be read in.
450
451 \begin{code}
452 ppUpdateInfo NoUpdateInfo          = empty
453 ppUpdateInfo (SomeUpdateInfo [])   = empty
454 ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("__U ")) (hcat (map int spec))
455 \end{code}
456
457 %************************************************************************
458 %*                                                                      *
459 \subsection[CAF-IdInfo]{CAF-related information}
460 %*                                                                      *
461 %************************************************************************
462
463 This information is used to build Static Reference Tables (see
464 simplStg/ComputeSRT.lhs).
465
466 \begin{code}
467 data CafInfo 
468         = MayHaveCafRefs                -- either:
469                                         -- (1) A function or static constructor
470                                         --     that refers to one or more CAFs,
471                                         -- (2) A real live CAF
472
473         | NoCafRefs                     -- A function or static constructor
474                                         -- that refers to no CAFs.
475
476 -- LATER: not sure how easy this is...
477 --      | OneCafRef Id
478
479
480 ppCafInfo NoCafRefs = ptext SLIT("__C")
481 ppCafInfo MayHaveCafRefs = empty
482 \end{code}
483
484
485 %************************************************************************
486 %*                                                                      *
487 \subsection[CAF-IdInfo]{CAF-related information}
488 %*                                                                      *
489 %************************************************************************
490
491 zapFragileIdInfo is used when cloning binders, mainly in the
492 simplifier.  We must forget about used-once information because that
493 isn't necessarily correct in the transformed program.
494 Also forget specialisations and unfoldings because they would need
495 substitution to be correct.  (They get pinned back on separately.)
496
497 \begin{code}
498 zapFragileIdInfo :: IdInfo -> Maybe IdInfo
499 zapFragileIdInfo info@(IdInfo {inlinePragInfo   = inline_prag, 
500                                specInfo         = rules, 
501                                unfoldingInfo    = unfolding})
502   |  not is_fragile_inline_prag 
503         -- We must forget about whether it was marked safe-to-inline,
504         -- because that isn't necessarily true in the simplified expression.
505         -- This is important because expressions may  be re-simplified
506
507   && isEmptyCoreRules rules
508         -- Specialisations would need substituting.  They get pinned
509         -- back on separately.
510
511   && not (hasUnfolding unfolding)
512         -- This is very important; occasionally a let-bound binder is used
513         -- as a binder in some lambda, in which case its unfolding is utterly
514         -- bogus.  Also the unfolding uses old binders so if we left it we'd
515         -- have to substitute it. Much better simply to give the Id a new
516         -- unfolding each time, which is what the simplifier does.
517   = Nothing
518
519   | otherwise
520   = Just (info {inlinePragInfo  = safe_inline_prag, 
521                 specInfo        = emptyCoreRules,
522                 unfoldingInfo   = noUnfolding})
523
524   where
525     is_fragile_inline_prag = case inline_prag of
526                                 ICanSafelyBeINLINEd _ _ -> True
527
528 -- We used to say the dead-ness was fragile, but I don't
529 -- see why it is.  Furthermore, deadness is a pain to lose;
530 -- see Simplify.mkDupableCont (Select ...)
531 --                              IAmDead                 -> True
532
533                                 other                   -> False
534
535         -- Be careful not to destroy real 'pragma' info
536     safe_inline_prag | is_fragile_inline_prag = NoInlinePragInfo
537                      | otherwise              = inline_prag
538 \end{code}
539
540
541 @zapLamIdInfo@ is used for lambda binders that turn out to to be
542 part of an unsaturated lambda
543
544 \begin{code}
545 zapLamIdInfo :: IdInfo -> Maybe IdInfo
546 zapLamIdInfo info@(IdInfo {inlinePragInfo = inline_prag, demandInfo = demand})
547   | is_safe_inline_prag && not (isStrict demand)
548   = Nothing
549   | otherwise
550   = Just (info {inlinePragInfo = safe_inline_prag,
551                 demandInfo = wwLazy})
552   where
553         -- The "unsafe" prags are the ones that say I'm not in a lambda
554         -- because that might not be true for an unsaturated lambda
555     is_safe_inline_prag = case inline_prag of
556                                 ICanSafelyBeINLINEd NotInsideLam nalts -> False
557                                 other                                  -> True
558
559     safe_inline_prag    = case inline_prag of
560                                 ICanSafelyBeINLINEd _ nalts
561                                       -> ICanSafelyBeINLINEd InsideLam nalts
562                                 other -> inline_prag
563 \end{code}
564
565
566 %************************************************************************
567 %*                                                                      *
568 \subsection[cpr-IdInfo]{Constructed Product Result info about an @Id@}
569 %*                                                                      *
570 %************************************************************************
571
572 If the @Id@ is a function then it may have CPR info. A CPR analysis
573 phase detects whether:
574
575 \begin{enumerate}
576 \item
577 The function's return value has a product type, i.e. an algebraic  type 
578 with a single constructor. Examples of such types are tuples and boxed
579 primitive values.
580 \item
581 The function always 'constructs' the value that it is returning.  It
582 must do this on every path through,  and it's OK if it calls another
583 function which constructs the result.
584 \end{enumerate}
585
586 If this is the case then we store a template which tells us the
587 function has the CPR property and which components of the result are
588 also CPRs.   
589
590 \begin{code}
591 data CprInfo
592   = NoCPRInfo
593
594   | CPRInfo [CprInfo] 
595
596 -- e.g. const 5 == CPRInfo [NoCPRInfo]
597 --              == __M(-)
598 --      \x -> (5,
599 --              (x,
600 --               5,
601 --               x)
602 --            ) 
603 --            CPRInfo [CPRInfo [NoCPRInfo], 
604 --                     CPRInfo [NoCprInfo,
605 --                              CPRInfo [NoCPRInfo],
606 --                              NoCPRInfo]
607 --                    ]
608 --            __M((-)(-(-)-)-)
609 \end{code}
610
611 \begin{code}
612
613 noCprInfo       = NoCPRInfo
614
615 ppCprInfo NoCPRInfo = empty
616 ppCprInfo c@(CPRInfo _)
617   = hsep [ptext SLIT("__M"), ppCprInfo' c]
618     where
619     ppCprInfo' NoCPRInfo      = char '-'
620     ppCprInfo' (CPRInfo args) = parens (hcat (map ppCprInfo' args))
621
622 instance Outputable CprInfo where
623     ppr = ppCprInfo
624
625 instance Show CprInfo where
626     showsPrec p c = showsPrecSDoc p (ppr c)
627 \end{code}
628
629
630 %************************************************************************
631 %*                                                                      *
632 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
633 %*                                                                      *
634 %************************************************************************
635
636 If the @Id@ is a lambda-bound variable then it may have lambda-bound
637 var info.  The usage analysis (UsageSP) detects whether the lambda
638 binding this var is a ``one-shot'' lambda; that is, whether it is
639 applied at most once.
640
641 This information may be useful in optimisation, as computations may
642 safely be floated inside such a lambda without risk of duplicating
643 work.
644
645 \begin{code}
646 data LBVarInfo
647   = NoLBVarInfo
648
649   | IsOneShotLambda             -- The lambda that binds this Id is applied
650                                 --   at most once
651                                 -- HACK ALERT! placing this info here is a short-term hack,
652                                 --   but it minimises changes to the rest of the compiler.
653                                 --   Hack agreed by SLPJ/KSW 1999-04.
654 \end{code}
655
656 \begin{code}
657 noLBVarInfo = NoLBVarInfo
658
659 -- not safe to print or parse LBVarInfo because it is not really a
660 -- property of the definition, but a property of the context.
661 ppLBVarInfo _ = empty
662
663 instance Outputable LBVarInfo where
664     ppr = ppLBVarInfo
665
666 instance Show LBVarInfo where
667     showsPrec p c = showsPrecSDoc p (ppr c)
668 \end{code}