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