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