[project @ 2000-03-27 13:24:12 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         IdInfo,         -- Abstract
12
13         vanillaIdInfo, mkIdInfo, seqIdInfo, megaSeqIdInfo,
14
15         -- Zapping
16         zapFragileInfo, zapLamInfo, zapSpecPragInfo, copyIdInfo,
17
18         -- Flavour
19         IdFlavour(..), flavourInfo, 
20         setNoDiscardInfo,
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
33         strictnessInfo, setStrictnessInfo,      
34
35         -- Worker
36         WorkerInfo(..), workerExists, wrapperArity, workerId,
37         workerInfo, setWorkerInfo, ppWorkerInfo,
38
39         -- Unfolding
40         unfoldingInfo, setUnfoldingInfo, 
41
42         -- DemandInfo
43         demandInfo, setDemandInfo, 
44
45         -- Inline prags
46         InlinePragInfo(..), 
47         inlinePragInfo, setInlinePragInfo, pprInlinePragInfo,
48
49         -- Occurrence info
50         OccInfo(..), isFragileOccInfo,
51         InsideLam, OneBranch, insideLam, notInsideLam, oneBranch, notOneBranch,
52         occInfo, setOccInfo, 
53
54         -- Specialisation
55         specInfo, setSpecInfo,
56
57         -- Update
58         UpdateInfo, UpdateSpec,
59         mkUpdateInfo, updateInfo, updateInfoMaybe, ppUpdateInfo, setUpdateInfo,
60
61         -- CAF info
62         CafInfo(..), cafInfo, setCafInfo, ppCafInfo,
63
64         -- Constructed Product Result Info
65         CprInfo(..), cprInfo, setCprInfo, ppCprInfo, noCprInfo,
66
67         -- Lambda-bound variable info
68         LBVarInfo(..), lbvarInfo, setLBVarInfo, noLBVarInfo
69     ) where
70
71 #include "HsVersions.h"
72
73
74 import CoreSyn
75 import PrimOp           ( PrimOp )
76 import Var              ( Id )
77 import BasicTypes       ( OccInfo(..), isFragileOccInfo, seqOccInfo,
78                           InsideLam, insideLam, notInsideLam, 
79                           OneBranch, oneBranch, notOneBranch,
80                           Arity
81                         )
82 import DataCon          ( DataCon )
83 import FieldLabel       ( FieldLabel )
84 import Demand           -- Lots of stuff
85 import Outputable       
86 import Maybe            ( isJust )
87
88 infixl  1 `setUpdateInfo`,
89           `setDemandInfo`,
90           `setStrictnessInfo`,
91           `setSpecInfo`,
92           `setArityInfo`,
93           `setInlinePragInfo`,
94           `setUnfoldingInfo`,
95           `setCprInfo`,
96           `setWorkerInfo`,
97           `setCafInfo`,
98           `setOccInfo`
99         -- infixl so you can say (id `set` a `set` b)
100 \end{code}
101
102 An @IdInfo@ gives {\em optional} information about an @Id@.  If
103 present it never lies, but it may not be present, in which case there
104 is always a conservative assumption which can be made.
105
106         There is one exception: the 'flavour' is *not* optional.
107         You must not discard it.
108         It used to be in Var.lhs, but that seems unclean.
109
110 Two @Id@s may have different info even though they have the same
111 @Unique@ (and are hence the same @Id@); for example, one might lack
112 the properties attached to the other.
113
114 The @IdInfo@ gives information about the value, or definition, of the
115 @Id@.  It does {\em not} contain information about the @Id@'s usage
116 (except for @DemandInfo@? ToDo). (@lbvarInfo@ is also a marginal
117 case.  KSW 1999-04).
118
119 \begin{code}
120 data IdInfo
121   = IdInfo {
122         flavourInfo     :: IdFlavour,           -- NOT OPTIONAL
123         arityInfo       :: ArityInfo,           -- Its arity
124         demandInfo      :: Demand,              -- Whether or not it is definitely demanded
125         specInfo        :: CoreRules,           -- Specialisations of this function which exist
126         strictnessInfo  :: StrictnessInfo,      -- Strictness properties
127         workerInfo      :: WorkerInfo,          -- Pointer to Worker Function
128         unfoldingInfo   :: Unfolding,           -- Its unfolding
129         updateInfo      :: UpdateInfo,          -- Which args should be updated
130         cafInfo         :: CafInfo,
131         cprInfo         :: CprInfo,             -- Function always constructs a product result
132         lbvarInfo       :: LBVarInfo,           -- Info about a lambda-bound variable
133         inlinePragInfo  :: InlinePragInfo,      -- Inline pragma
134         occInfo         :: OccInfo              -- How it occurs
135     }
136
137 seqIdInfo :: IdInfo -> ()
138 seqIdInfo (IdInfo {}) = ()
139
140 megaSeqIdInfo :: IdInfo -> ()
141 megaSeqIdInfo info
142   = seqFlavour (flavourInfo info)               `seq`
143     seqArity (arityInfo info)                   `seq`
144     seqDemand (demandInfo info)                 `seq`
145     seqRules (specInfo info)                    `seq`
146     seqStrictnessInfo (strictnessInfo info)     `seq`
147     seqWorker (workerInfo info)                 `seq`
148
149 --    seqUnfolding (unfoldingInfo info) `seq`
150 -- Omitting this improves runtimes a little, presumably because
151 -- some unfoldings are not calculated at all
152
153     seqCaf (cafInfo info)               `seq`
154     seqCpr (cprInfo info)               `seq`
155     seqLBVar (lbvarInfo info)           `seq`
156     seqOccInfo (occInfo info) 
157 \end{code}
158
159 Setters
160
161 \begin{code}
162 setWorkerInfo     info wk = wk `seq` info { workerInfo = wk }
163 setSpecInfo       info sp = PSEQ sp (info { specInfo = sp })
164 setInlinePragInfo info pr = pr `seq` info { inlinePragInfo = pr }
165 setOccInfo        info oc = oc `seq` info { occInfo = oc }
166 setStrictnessInfo info st = st `seq` info { strictnessInfo = st }
167         -- Try to avoid spack leaks by seq'ing
168
169 setUnfoldingInfo  info uf = info { unfoldingInfo = uf }
170         -- We do *not* seq on the unfolding info, For some reason, doing so 
171         -- actually increases residency significantly. 
172
173 setUpdateInfo     info ud = info { updateInfo = ud }
174 setDemandInfo     info dd = info { demandInfo = dd }
175 setArityInfo      info ar = info { arityInfo = ar  }
176 setCafInfo        info cf = info { cafInfo = cf }
177 setCprInfo        info cp = info { cprInfo = cp }
178 setLBVarInfo      info lb = info { lbvarInfo = lb }
179
180 setNoDiscardInfo  info = case flavourInfo info of
181                                 VanillaId -> info { flavourInfo = NoDiscardId }
182                                 other     -> info
183 zapSpecPragInfo   info = case flavourInfo info of
184                                 SpecPragmaId -> info { flavourInfo = VanillaId }
185                                 other        -> info
186 \end{code}
187
188
189 \begin{code}
190 vanillaIdInfo :: IdInfo
191 vanillaIdInfo = mkIdInfo VanillaId
192
193 mkIdInfo :: IdFlavour -> IdInfo
194 mkIdInfo flv = IdInfo {
195                     flavourInfo         = flv,
196                     arityInfo           = UnknownArity,
197                     demandInfo          = wwLazy,
198                     specInfo            = emptyCoreRules,
199                     workerInfo          = NoWorker,
200                     strictnessInfo      = NoStrictnessInfo,
201                     unfoldingInfo       = noUnfolding,
202                     updateInfo          = NoUpdateInfo,
203                     cafInfo             = MayHaveCafRefs,
204                     cprInfo             = NoCPRInfo,
205                     lbvarInfo           = NoLBVarInfo,
206                     inlinePragInfo      = NoInlinePragInfo,
207                     occInfo             = NoOccInfo
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   | DataConId DataCon           -- The Id for a data constructor *worker*
222   | DataConWrapId DataCon       -- The Id for a data constructor *wrapper*
223                                 -- [the only reasons we need to know is so that
224                                 --  a) we can  suppress printing a definition in the interface file
225                                 --  b) when typechecking a pattern we can get from the
226                                 --     Id back to the data con]
227   | PrimOpId PrimOp             -- The Id for a primitive operator
228   | RecordSelId FieldLabel      -- The Id for a record selector
229   | SpecPragmaId                -- Don't discard these
230   | NoDiscardId                 -- Don't discard these either
231
232 ppFlavourInfo :: IdFlavour -> SDoc
233 ppFlavourInfo VanillaId         = empty
234 ppFlavourInfo (DataConId _)     = ptext SLIT("[DataCon]")
235 ppFlavourInfo (DataConWrapId _) = ptext SLIT("[DataConWrapper]")
236 ppFlavourInfo (PrimOpId _)      = ptext SLIT("[PrimOp]")
237 ppFlavourInfo (RecordSelId _)   = ptext SLIT("[RecSel]")
238 ppFlavourInfo SpecPragmaId      = ptext SLIT("[SpecPrag]")
239 ppFlavourInfo NoDiscardId       = ptext SLIT("[NoDiscard]")
240
241 seqFlavour :: IdFlavour -> ()
242 seqFlavour f = f `seq` ()
243 \end{code}
244
245 The @SpecPragmaId@ exists only to make Ids that are
246 on the *LHS* of bindings created by SPECIALISE pragmas; 
247 eg:             s = f Int d
248 The SpecPragmaId is never itself mentioned; it
249 exists solely so that the specialiser will find
250 the call to f, and make specialised version of it.
251 The SpecPragmaId binding is discarded by the specialiser
252 when it gathers up overloaded calls.
253 Meanwhile, it is not discarded as dead code.
254
255
256 %************************************************************************
257 %*                                                                      *
258 \subsection[arity-IdInfo]{Arity info about an @Id@}
259 %*                                                                      *
260 %************************************************************************
261
262 For locally-defined Ids, the code generator maintains its own notion
263 of their arities; so it should not be asking...  (but other things
264 besides the code-generator need arity info!)
265
266 \begin{code}
267 data ArityInfo
268   = UnknownArity        -- No idea
269
270   | ArityExactly Arity  -- Arity is exactly this.  We use this when importing a
271                         -- function; it's already been compiled and we know its
272                         -- arity for sure.
273
274   | ArityAtLeast Arity  -- Arity is this or greater.  We attach this arity to 
275                         -- functions in the module being compiled.  Their arity
276                         -- might increase later in the compilation process, if
277                         -- an extra lambda floats up to the binding site.
278
279 seqArity :: ArityInfo -> ()
280 seqArity a = arityLowerBound a `seq` ()
281
282 exactArity   = ArityExactly
283 atLeastArity = ArityAtLeast
284 unknownArity = UnknownArity
285
286 arityLowerBound :: ArityInfo -> Arity
287 arityLowerBound UnknownArity     = 0
288 arityLowerBound (ArityAtLeast n) = n
289 arityLowerBound (ArityExactly n) = n
290
291 hasArity :: ArityInfo -> Bool
292 hasArity UnknownArity = False
293 hasArity other        = True
294
295 ppArityInfo UnknownArity         = empty
296 ppArityInfo (ArityExactly arity) = hsep [ptext SLIT("__A"), int arity]
297 ppArityInfo (ArityAtLeast arity) = hsep [ptext SLIT("__AL"), int arity]
298 \end{code}
299
300 %************************************************************************
301 %*                                                                      *
302 \subsection{Inline-pragma information}
303 %*                                                                      *
304 %************************************************************************
305
306 \begin{code}
307 data InlinePragInfo
308   = NoInlinePragInfo
309   | IMustNotBeINLINEd Bool              -- True <=> came from an INLINE prag, False <=> came from a NOINLINE prag
310                       (Maybe Int)       -- Phase number from pragma, if any
311         -- The True, Nothing case doesn't need to be recorded
312
313 instance Outputable InlinePragInfo where
314   -- This is now parsed in interface files
315   ppr NoInlinePragInfo = empty
316   ppr other_prag       = ptext SLIT("__U") <> pprInlinePragInfo other_prag
317
318 pprInlinePragInfo NoInlinePragInfo                   = empty
319 pprInlinePragInfo (IMustNotBeINLINEd True Nothing)   = empty
320 pprInlinePragInfo (IMustNotBeINLINEd True (Just n))  = brackets (int n)
321 pprInlinePragInfo (IMustNotBeINLINEd False Nothing)  = brackets (char '!')
322 pprInlinePragInfo (IMustNotBeINLINEd False (Just n)) = brackets (char '!' <> int n)
323                                                         
324 instance Show InlinePragInfo where
325   showsPrec p prag = showsPrecSDoc p (ppr prag)
326 \end{code}
327
328
329 %************************************************************************
330 %*                                                                      *
331 \subsection[worker-IdInfo]{Worker info about an @Id@}
332 %*                                                                      *
333 %************************************************************************
334
335 If this Id has a worker then we store a reference to it. Worker
336 functions are generated by the worker/wrapper pass.  This uses
337 information from the strictness and CPR analyses.
338
339 There might not be a worker, even for a strict function, because:
340 (a) the function might be small enough to inline, so no need 
341     for w/w split
342 (b) the strictness info might be "SSS" or something, so no w/w split.
343
344 \begin{code}
345
346 data WorkerInfo = NoWorker
347                 | HasWorker Id Arity
348         -- The Arity is the arity of the *wrapper* at the moment of the
349         -- w/w split. It had better be the same as the arity of the wrapper
350         -- at the moment it is spat into the interface file.
351         -- This Arity just lets us make a (hopefully redundant) sanity check
352
353 seqWorker :: WorkerInfo -> ()
354 seqWorker (HasWorker id _) = id `seq` ()
355 seqWorker NoWorker         = ()
356
357 ppWorkerInfo NoWorker            = empty
358 ppWorkerInfo (HasWorker wk_id _) = ptext SLIT("__P") <+> ppr wk_id
359
360 noWorkerInfo = NoWorker
361
362 workerExists :: WorkerInfo -> Bool
363 workerExists NoWorker        = False
364 workerExists (HasWorker _ _) = True
365
366 workerId :: WorkerInfo -> Id
367 workerId (HasWorker id _) = id
368
369 wrapperArity :: WorkerInfo -> Arity
370 wrapperArity (HasWorker _ a) = a
371 \end{code}
372
373
374 %************************************************************************
375 %*                                                                      *
376 \subsection[update-IdInfo]{Update-analysis info about an @Id@}
377 %*                                                                      *
378 %************************************************************************
379
380 \begin{code}
381 data UpdateInfo
382   = NoUpdateInfo
383   | SomeUpdateInfo UpdateSpec
384   deriving (Eq, Ord)
385       -- we need Eq/Ord to cross-chk update infos in interfaces
386
387 -- the form in which we pass update-analysis info between modules:
388 type UpdateSpec = [Int]
389 \end{code}
390
391 \begin{code}
392 mkUpdateInfo = SomeUpdateInfo
393
394 updateInfoMaybe NoUpdateInfo        = Nothing
395 updateInfoMaybe (SomeUpdateInfo []) = Nothing
396 updateInfoMaybe (SomeUpdateInfo  u) = Just u
397 \end{code}
398
399 Text instance so that the update annotations can be read in.
400
401 \begin{code}
402 ppUpdateInfo NoUpdateInfo          = empty
403 ppUpdateInfo (SomeUpdateInfo [])   = empty
404 ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("__UA ")) (hcat (map int spec))
405   -- was "__U "; changed to avoid conflict with unfoldings.  KSW 1999-07.
406 \end{code}
407
408 %************************************************************************
409 %*                                                                      *
410 \subsection[CAF-IdInfo]{CAF-related information}
411 %*                                                                      *
412 %************************************************************************
413
414 This information is used to build Static Reference Tables (see
415 simplStg/ComputeSRT.lhs).
416
417 \begin{code}
418 data CafInfo 
419         = MayHaveCafRefs                -- either:
420                                         -- (1) A function or static constructor
421                                         --     that refers to one or more CAFs,
422                                         -- (2) A real live CAF
423
424         | NoCafRefs                     -- A function or static constructor
425                                         -- that refers to no CAFs.
426
427 -- LATER: not sure how easy this is...
428 --      | OneCafRef Id
429
430
431 seqCaf c = c `seq` ()
432
433 ppCafInfo NoCafRefs = ptext SLIT("__C")
434 ppCafInfo MayHaveCafRefs = empty
435 \end{code}
436
437
438 %************************************************************************
439 %*                                                                      *
440 \subsection[cpr-IdInfo]{Constructed Product Result info about an @Id@}
441 %*                                                                      *
442 %************************************************************************
443
444 If the @Id@ is a function then it may have CPR info. A CPR analysis
445 phase detects whether:
446
447 \begin{enumerate}
448 \item
449 The function's return value has a product type, i.e. an algebraic  type 
450 with a single constructor. Examples of such types are tuples and boxed
451 primitive values.
452 \item
453 The function always 'constructs' the value that it is returning.  It
454 must do this on every path through,  and it's OK if it calls another
455 function which constructs the result.
456 \end{enumerate}
457
458 If this is the case then we store a template which tells us the
459 function has the CPR property and which components of the result are
460 also CPRs.   
461
462 \begin{code}
463 data CprInfo
464   = NoCPRInfo
465   | ReturnsCPR  -- Yes, this function returns a constructed product
466                 -- Implicitly, this means "after the function has been applied
467                 -- to all its arguments", so the worker/wrapper builder in 
468                 -- WwLib.mkWWcpr checks that that it is indeed saturated before
469                 -- making use of the CPR info
470
471         -- We used to keep nested info about sub-components, but
472         -- we never used it so I threw it away
473 \end{code}
474
475 \begin{code}
476 seqCpr :: CprInfo -> ()
477 seqCpr ReturnsCPR = ()
478 seqCpr NoCPRInfo  = ()
479
480 noCprInfo       = NoCPRInfo
481
482 ppCprInfo NoCPRInfo  = empty
483 ppCprInfo ReturnsCPR = ptext SLIT("__M")
484
485 instance Outputable CprInfo where
486     ppr = ppCprInfo
487
488 instance Show CprInfo where
489     showsPrec p c = showsPrecSDoc p (ppr c)
490 \end{code}
491
492
493 %************************************************************************
494 %*                                                                      *
495 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
496 %*                                                                      *
497 %************************************************************************
498
499 If the @Id@ is a lambda-bound variable then it may have lambda-bound
500 var info.  The usage analysis (UsageSP) detects whether the lambda
501 binding this var is a ``one-shot'' lambda; that is, whether it is
502 applied at most once.
503
504 This information may be useful in optimisation, as computations may
505 safely be floated inside such a lambda without risk of duplicating
506 work.
507
508 \begin{code}
509 data LBVarInfo
510   = NoLBVarInfo
511
512   | IsOneShotLambda             -- The lambda that binds this Id is applied
513                                 --   at most once
514                                 -- HACK ALERT! placing this info here is a short-term hack,
515                                 --   but it minimises changes to the rest of the compiler.
516                                 --   Hack agreed by SLPJ/KSW 1999-04.
517
518 seqLBVar l = l `seq` ()
519 \end{code}
520
521 \begin{code}
522 noLBVarInfo = NoLBVarInfo
523
524 -- not safe to print or parse LBVarInfo because it is not really a
525 -- property of the definition, but a property of the context.
526 pprLBVarInfo NoLBVarInfo     = empty
527 pprLBVarInfo IsOneShotLambda = getPprStyle $ \ sty ->
528                                if ifaceStyle sty then empty
529                                                  else ptext SLIT("OneShot")
530
531 instance Outputable LBVarInfo where
532     ppr = pprLBVarInfo
533
534 instance Show LBVarInfo where
535     showsPrec p c = showsPrecSDoc p (ppr c)
536 \end{code}
537
538
539 %************************************************************************
540 %*                                                                      *
541 \subsection{Bulk operations on IdInfo}
542 %*                                                                      *
543 %************************************************************************
544
545 zapFragileInfo is used when cloning binders, mainly in the
546 simplifier.  We must forget about used-once information because that
547 isn't necessarily correct in the transformed program.
548 Also forget specialisations and unfoldings because they would need
549 substitution to be correct.  (They get pinned back on separately.)
550
551 \begin{code}
552 zapFragileInfo :: IdInfo -> Maybe IdInfo
553 zapFragileInfo info@(IdInfo {occInfo            = occ, 
554                              workerInfo         = wrkr,
555                              specInfo           = rules, 
556                              unfoldingInfo      = unfolding})
557   |  not (isFragileOccInfo occ)
558         -- We must forget about whether it was marked safe-to-inline,
559         -- because that isn't necessarily true in the simplified expression.
560         -- This is important because expressions may  be re-simplified
561         -- We don't zap deadness or loop-breaker-ness.
562         -- The latter is important because it tells MkIface not to 
563         -- spit out an inlining for the thing.  The former doesn't
564         -- seem so important, but there's no harm.
565
566   && isEmptyCoreRules rules
567         -- Specialisations would need substituting.  They get pinned
568         -- back on separately.
569
570   && not (workerExists wrkr)
571
572   && not (hasUnfolding unfolding)
573         -- This is very important; occasionally a let-bound binder is used
574         -- as a binder in some lambda, in which case its unfolding is utterly
575         -- bogus.  Also the unfolding uses old binders so if we left it we'd
576         -- have to substitute it. Much better simply to give the Id a new
577         -- unfolding each time, which is what the simplifier does.
578   = Nothing
579
580   | otherwise
581   = Just (info {occInfo         = robust_occ_info,
582                 workerInfo      = noWorkerInfo,
583                 specInfo        = emptyCoreRules,
584                 unfoldingInfo   = noUnfolding})
585   where
586         -- It's important to keep the loop-breaker info,
587         -- because the substitution doesn't remember it.
588     robust_occ_info = case occ of
589                         OneOcc _ _ -> NoOccInfo
590                         other      -> occ
591 \end{code}
592
593 @zapLamInfo@ is used for lambda binders that turn out to to be
594 part of an unsaturated lambda
595
596 \begin{code}
597 zapLamInfo :: IdInfo -> Maybe IdInfo
598 zapLamInfo info@(IdInfo {occInfo = occ, demandInfo = demand})
599   | is_safe_occ && not (isStrict demand)
600   = Nothing
601   | otherwise
602   = Just (info {occInfo = safe_occ,
603                 demandInfo = wwLazy})
604   where
605         -- The "unsafe" occ info is the ones that say I'm not in a lambda
606         -- because that might not be true for an unsaturated lambda
607     is_safe_occ = case occ of
608                         OneOcc in_lam once -> in_lam
609                         other              -> True
610
611     safe_occ = case occ of
612                  OneOcc _ once -> OneOcc insideLam once
613                  other         -> occ
614 \end{code}
615
616
617 copyIdInfo is used when shorting out a top-level binding
618         f_local = BIG
619         f = f_local
620 where f is exported.  We are going to swizzle it around to
621         f = BIG
622         f_local = f
623 but we must be careful to combine their IdInfos right.
624 The fact that things can go wrong here is a bad sign, but I can't see
625 how to make it 'patently right', so copyIdInfo is derived (pretty much) by trial and error
626
627 Here 'from' is f_local, 'to' is f, and the result is attached to f
628
629 \begin{code}
630 copyIdInfo :: IdInfo    -- From
631            -> IdInfo    -- To
632            -> IdInfo    -- To, updated with stuff from From; except flavour unchanged
633 copyIdInfo from to = from { flavourInfo = flavourInfo to,
634                             specInfo = specInfo to,
635                             inlinePragInfo = inlinePragInfo to
636                           }
637         -- It's important to preserve the inline pragma on 'f'; e.g. consider
638         --      {-# NOINLINE f #-}
639         --      f = local
640         --
641         -- similarly, transformation rules may be attached to f
642         -- and we want to preserve them.  
643         --
644         -- On the other hand, we want the strictness info from f_local.
645 \end{code}