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