[project @ 1999-07-15 14:08:03 by keithw]
[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         -- Flavour
16         IdFlavour(..), flavourInfo, 
17         setNoDiscardInfo, zapSpecPragInfo, copyIdInfo,
18         ppFlavourInfo,
19
20         -- Arity
21         ArityInfo(..),
22         exactArity, atLeastArity, unknownArity, hasArity,
23         arityInfo, setArityInfo, ppArityInfo, arityLowerBound,
24
25         -- Strictness
26         StrictnessInfo(..),                             -- Non-abstract
27         mkStrictnessInfo,
28         noStrictnessInfo, strictnessInfo,
29         ppStrictnessInfo, setStrictnessInfo, 
30         isBottomingStrictness, appIsBottom,
31
32         -- Worker
33         WorkerInfo, workerExists, 
34         workerInfo, setWorkerInfo, ppWorkerInfo,
35
36         -- Unfolding
37         unfoldingInfo, setUnfoldingInfo, 
38
39         -- DemandInfo
40         demandInfo, setDemandInfo, 
41
42         -- Inline prags
43         InlinePragInfo(..), OccInfo(..),
44         inlinePragInfo, setInlinePragInfo, notInsideLambda,
45
46         -- Specialisation
47         specInfo, setSpecInfo,
48
49         -- Update
50         UpdateInfo, UpdateSpec,
51         mkUpdateInfo, updateInfo, updateInfoMaybe, ppUpdateInfo, setUpdateInfo,
52
53         -- CAF info
54         CafInfo(..), cafInfo, setCafInfo, ppCafInfo,
55
56         -- Constructed Product Result Info
57         CprInfo(..), cprInfo, setCprInfo, ppCprInfo, noCprInfo,
58
59         -- Zapping
60         zapLamIdInfo, zapFragileIdInfo, zapIdInfoForStg,
61
62         -- Lambda-bound variable info
63         LBVarInfo(..), lbvarInfo, setLBVarInfo, noLBVarInfo
64     ) where
65
66 #include "HsVersions.h"
67
68
69 import {-# SOURCE #-} CoreUnfold ( Unfolding, noUnfolding, hasUnfolding, seqUnfolding )
70 import {-# SOURCE #-} CoreSyn    ( CoreExpr, CoreRules, emptyCoreRules, isEmptyCoreRules, seqRules )
71 import {-# SOURCE #-} Const      ( Con )
72
73 import Var              ( Id )
74 import FieldLabel       ( FieldLabel )
75 import Demand           ( Demand, isStrict, isLazy, wwLazy, pprDemands, seqDemand, seqDemands )
76 import Type             ( UsageAnn )
77 import Outputable       
78 import Maybe            ( isJust )
79
80 infixl  1 `setUpdateInfo`,
81           `setDemandInfo`,
82           `setStrictnessInfo`,
83           `setSpecInfo`,
84           `setArityInfo`,
85           `setInlinePragInfo`,
86           `setUnfoldingInfo`,
87           `setCprInfo`,
88           `setWorkerInfo`,
89           `setCafInfo`
90         -- infixl so you can say (id `set` a `set` b)
91 \end{code}
92
93 An @IdInfo@ gives {\em optional} information about an @Id@.  If
94 present it never lies, but it may not be present, in which case there
95 is always a conservative assumption which can be made.
96
97         There is one exception: the 'flavour' is *not* optional.
98         You must not discard it.
99         It used to be in Var.lhs, but that seems unclean.
100
101 Two @Id@s may have different info even though they have the same
102 @Unique@ (and are hence the same @Id@); for example, one might lack
103 the properties attached to the other.
104
105 The @IdInfo@ gives information about the value, or definition, of the
106 @Id@.  It does {\em not} contain information about the @Id@'s usage
107 (except for @DemandInfo@? ToDo). (@lbvarInfo@ is also a marginal
108 case.  KSW 1999-04).
109
110 \begin{code}
111 data IdInfo
112   = IdInfo {
113         flavourInfo     :: IdFlavour,           -- NOT OPTIONAL
114         arityInfo       :: ArityInfo,           -- Its arity
115         demandInfo      :: Demand,              -- Whether or not it is definitely demanded
116         specInfo        :: CoreRules,           -- Specialisations of this function which exist
117         strictnessInfo  :: StrictnessInfo,      -- Strictness properties
118         workerInfo      :: WorkerInfo,          -- Pointer to Worker Function
119         unfoldingInfo   :: Unfolding,           -- Its unfolding
120         updateInfo      :: UpdateInfo,          -- Which args should be updated
121         cafInfo         :: CafInfo,
122         cprInfo         :: CprInfo,             -- Function always constructs a product result
123         lbvarInfo       :: LBVarInfo,           -- Info about a lambda-bound variable
124         inlinePragInfo  :: InlinePragInfo       -- Inline pragmas
125     }
126
127 seqIdInfo :: IdInfo -> ()
128 seqIdInfo (IdInfo {}) = ()
129
130 megaSeqIdInfo :: IdInfo -> ()
131 megaSeqIdInfo info
132   = seqFlavour (flavourInfo info)       `seq`
133     seqArity (arityInfo info)           `seq`
134     seqDemand (demandInfo info)         `seq`
135     seqRules (specInfo info)            `seq`
136     seqStrictness (strictnessInfo info) `seq`
137     seqWorker (workerInfo info)         `seq`
138
139 --    seqUnfolding (unfoldingInfo info) `seq`
140 -- Omitting this improves runtimes a little, presumably because
141 -- some unfoldings are not calculated at all
142
143     seqCaf (cafInfo info)               `seq`
144     seqCpr (cprInfo info)               `seq`
145     seqLBVar (lbvarInfo info)           `seq`
146     seqInlinePrag (inlinePragInfo info) 
147 \end{code}
148
149 Setters
150
151 \begin{code}
152 setWorkerInfo     info wk = wk `seq` info { workerInfo = wk }
153 setSpecInfo       info sp = sp `seq` info { specInfo = sp }
154 setInlinePragInfo info pr = pr `seq` info { inlinePragInfo = pr }
155 setStrictnessInfo info st = st `seq` info { strictnessInfo = st }
156         -- Try to avoid spack leaks by seq'ing
157
158 setUnfoldingInfo  info uf = info { unfoldingInfo = uf }
159         -- We do *not* seq on the unfolding info, For some reason, doing so 
160         -- actually increases residency significantly. 
161
162 setUpdateInfo     info ud = info { updateInfo = ud }
163 setDemandInfo     info dd = info { demandInfo = dd }
164 setArityInfo      info ar = info { arityInfo = ar  }
165 setCafInfo        info cf = info { cafInfo = cf }
166 setCprInfo        info cp = info { cprInfo = cp }
167 setLBVarInfo      info lb = info { lbvarInfo = lb }
168
169 setNoDiscardInfo  info = case flavourInfo info of
170                                 VanillaId -> info { flavourInfo = NoDiscardId }
171                                 other     -> info
172 zapSpecPragInfo   info = case flavourInfo info of
173                                 SpecPragmaId -> info { flavourInfo = VanillaId }
174                                 other        -> info
175
176 copyIdInfo :: IdInfo    -- From
177            -> IdInfo    -- To
178            -> IdInfo    -- To updated with stuff from From; except flavour unchanged
179 -- copyIdInfo is used when shorting out a top-level binding
180 --      f_local = BIG
181 --      f = f_local
182 -- where f is exported.  We are going to swizzle it around to
183 --      f = BIG
184 --      f_local = f
185 -- but we must be careful to combine their IdInfos right.
186 -- The fact that things can go wrong here is a bad sign, but I can't see
187 -- how to make it 'patently right', so copyIdInfo is derived (pretty much) by trial and error
188 --
189 -- Here 'from' is f_local, 'to' is f.
190
191 copyIdInfo from to = from { flavourInfo = flavourInfo to,
192                             specInfo = specInfo to
193                           }
194         -- It's important to propagate the inline pragmas from bndr
195         -- to exportd_id.  Ditto strictness etc.  This "bites" when we use an INLNE pragma:
196         --      {-# INLINE f #-}
197         --      f x = (x,x)
198         --
199         -- This becomes (where the "*" means INLINE prag)
200         --
201         --      M.f = /\a -> let mf* = \x -> (x,x) in mf
202         --
203         -- Now the mf floats out and we end up with the trivial binding
204         --
205         --      mf* = /\a -> \x -> (x,x)
206         --      M.f = mf
207         --
208         -- Now, when we short out the M.f = mf binding we must preserve the inline
209         -- pragma on the mf binding.
210         --
211         -- On the other hand, transformation rules may be attached to the 
212         -- 'to' Id, and we want to preserve them.  
213 \end{code}
214
215
216 \begin{code}
217 vanillaIdInfo :: IdInfo
218 vanillaIdInfo = mkIdInfo VanillaId
219
220 mkIdInfo :: IdFlavour -> IdInfo
221 mkIdInfo flv = IdInfo {
222                     flavourInfo         = flv,
223                     arityInfo           = UnknownArity,
224                     demandInfo          = wwLazy,
225                     specInfo            = emptyCoreRules,
226                     workerInfo          = Nothing,
227                     strictnessInfo      = NoStrictnessInfo,
228                     unfoldingInfo       = noUnfolding,
229                     updateInfo          = NoUpdateInfo,
230                     cafInfo             = MayHaveCafRefs,
231                     cprInfo             = NoCPRInfo,
232                     lbvarInfo           = NoLBVarInfo,
233                     inlinePragInfo      = NoInlinePragInfo
234            }
235 \end{code}
236
237
238 %************************************************************************
239 %*                                                                      *
240 \subsection{Flavour}
241 %*                                                                      *
242 %************************************************************************
243
244 \begin{code}
245 data IdFlavour
246   = VanillaId                           -- Most Ids are like this
247   | ConstantId Con                      -- The Id for a constant (data constructor or primop)
248   | RecordSelId FieldLabel              -- The Id for a record selector
249   | SpecPragmaId                        -- Don't discard these
250   | NoDiscardId                         -- Don't discard these either
251
252 ppFlavourInfo :: IdFlavour -> SDoc
253 ppFlavourInfo VanillaId       = empty
254 ppFlavourInfo (ConstantId _)  = ptext SLIT("[Constr]")
255 ppFlavourInfo (RecordSelId _) = ptext SLIT("[RecSel]")
256 ppFlavourInfo SpecPragmaId    = ptext SLIT("[SpecPrag]")
257 ppFlavourInfo NoDiscardId     = ptext SLIT("[NoDiscard]")
258
259 seqFlavour :: IdFlavour -> ()
260 seqFlavour f = f `seq` ()
261 \end{code}
262
263 The @SpecPragmaId@ exists only to make Ids that are
264 on the *LHS* of bindings created by SPECIALISE pragmas; 
265 eg:             s = f Int d
266 The SpecPragmaId is never itself mentioned; it
267 exists solely so that the specialiser will find
268 the call to f, and make specialised version of it.
269 The SpecPragmaId binding is discarded by the specialiser
270 when it gathers up overloaded calls.
271 Meanwhile, it is not discarded as dead code.
272
273
274 %************************************************************************
275 %*                                                                      *
276 \subsection[arity-IdInfo]{Arity info about an @Id@}
277 %*                                                                      *
278 %************************************************************************
279
280 For locally-defined Ids, the code generator maintains its own notion
281 of their arities; so it should not be asking...  (but other things
282 besides the code-generator need arity info!)
283
284 \begin{code}
285 data ArityInfo
286   = UnknownArity        -- No idea
287   | ArityExactly Int    -- Arity is exactly this
288   | ArityAtLeast Int    -- Arity is this or greater
289
290 seqArity :: ArityInfo -> ()
291 seqArity a = arityLowerBound a `seq` ()
292
293 exactArity   = ArityExactly
294 atLeastArity = ArityAtLeast
295 unknownArity = UnknownArity
296
297 arityLowerBound :: ArityInfo -> Int
298 arityLowerBound UnknownArity     = 0
299 arityLowerBound (ArityAtLeast n) = n
300 arityLowerBound (ArityExactly n) = n
301
302 hasArity :: ArityInfo -> Bool
303 hasArity UnknownArity = False
304 hasArity other        = True
305
306 ppArityInfo UnknownArity         = empty
307 ppArityInfo (ArityExactly arity) = hsep [ptext SLIT("__A"), int arity]
308 ppArityInfo (ArityAtLeast arity) = hsep [ptext SLIT("__AL"), int arity]
309 \end{code}
310
311 %************************************************************************
312 %*                                                                      *
313 \subsection{Inline-pragma information}
314 %*                                                                      *
315 %************************************************************************
316
317 \begin{code}
318 data InlinePragInfo
319   = NoInlinePragInfo
320
321   | IMustNotBeINLINEd   -- User NOINLINE pragma
322
323   | IAmALoopBreaker     -- Used by the occurrence analyser to mark loop-breakers
324                         -- in a group of recursive definitions
325
326   | ICanSafelyBeINLINEd -- Used by the occurrence analyser to mark things
327                         -- that manifesly occur once, not inside SCCs, 
328                         -- not in constructor arguments
329
330         OccInfo         -- Says whether the occurrence is inside a lambda
331                         --      If so, must only substitute WHNFs
332
333         Bool            -- False <=> occurs in more than one case branch
334                         --      If so, there's a code-duplication issue
335
336   | IAmDead             -- Marks unused variables.  Sometimes useful for
337                         -- lambda and case-bound variables.
338
339   | IMustBeINLINEd      -- Absolutely must inline; used for PrimOps and
340                         -- constructors only.
341
342 seqInlinePrag :: InlinePragInfo -> ()
343 seqInlinePrag (ICanSafelyBeINLINEd occ alts) 
344   = occ `seq` alts `seq` ()
345 seqInlinePrag other
346   = ()
347
348 instance Outputable InlinePragInfo where
349   -- only used for debugging; never parsed.  KSW 1999-07
350   ppr NoInlinePragInfo          = empty
351   ppr IMustBeINLINEd            = ptext SLIT("__UU")
352   ppr IMustNotBeINLINEd         = ptext SLIT("__Unot")
353   ppr IAmALoopBreaker           = ptext SLIT("__Ux")
354   ppr IAmDead                   = ptext SLIT("__Ud")
355   ppr (ICanSafelyBeINLINEd InsideLam _) = ptext SLIT("__Ul")
356   ppr (ICanSafelyBeINLINEd _ _) = ptext SLIT("__Us")
357
358 instance Show InlinePragInfo where
359   showsPrec p prag = showsPrecSDoc p (ppr prag)
360 \end{code}
361
362 \begin{code}
363 data OccInfo
364   = NotInsideLam
365
366   | InsideLam           -- Inside a non-linear lambda (that is, a lambda which
367                         -- is sure to be instantiated only once).
368                         -- Substituting a redex for this occurrence is
369                         -- dangerous because it might duplicate work.
370
371 instance Outputable OccInfo where
372   ppr NotInsideLam = empty
373   ppr InsideLam    = text "l"
374
375
376 notInsideLambda :: OccInfo -> Bool
377 notInsideLambda NotInsideLam = True
378 notInsideLambda InsideLam    = False
379 \end{code}
380
381 %************************************************************************
382 %*                                                                      *
383 \subsection[strictness-IdInfo]{Strictness info about an @Id@}
384 %*                                                                      *
385 %************************************************************************
386
387 We specify the strictness of a function by giving information about
388 each of the ``wrapper's'' arguments (see the description about
389 worker/wrapper-style transformations in the PJ/Launchbury paper on
390 unboxed types).
391
392 The list of @Demands@ specifies: (a)~the strictness properties of a
393 function's arguments; and (b)~the type signature of that worker (if it
394 exists); i.e. its calling convention.
395
396 Note that the existence of a worker function is now denoted by the Id's
397 workerInfo field.
398
399 \begin{code}
400 data StrictnessInfo
401   = NoStrictnessInfo
402
403   | StrictnessInfo [Demand] 
404                    Bool         -- True <=> the function diverges regardless of its arguments
405                                 -- Useful for "error" and other disguised variants thereof.  
406                                 -- BUT NB: f = \x y. error "urk"
407                                 --         will have info  SI [SS] True
408                                 -- but still (f) and (f 2) are not bot; only (f 3 2) is bot
409
410 seqStrictness :: StrictnessInfo -> ()
411 seqStrictness (StrictnessInfo ds b) = b `seq` seqDemands ds
412 seqStrictness other                 = ()
413 \end{code}
414
415 \begin{code}
416 mkStrictnessInfo :: ([Demand], Bool) -> StrictnessInfo
417
418 mkStrictnessInfo (xs, is_bot)
419   | all isLazy xs && not is_bot = NoStrictnessInfo              -- Uninteresting
420   | otherwise                   = StrictnessInfo xs is_bot
421
422 noStrictnessInfo       = NoStrictnessInfo
423
424 isBottomingStrictness (StrictnessInfo _ bot) = bot
425 isBottomingStrictness NoStrictnessInfo       = False
426
427 -- appIsBottom returns true if an application to n args would diverge
428 appIsBottom (StrictnessInfo ds bot)   n = bot && (n >= length ds)
429 appIsBottom  NoStrictnessInfo         n = False
430
431 ppStrictnessInfo NoStrictnessInfo = empty
432 ppStrictnessInfo (StrictnessInfo wrapper_args bot)
433   = hsep [ptext SLIT("__S"), pprDemands wrapper_args bot]
434 \end{code}
435
436 %************************************************************************
437 %*                                                                      *
438 \subsection[worker-IdInfo]{Worker info about an @Id@}
439 %*                                                                      *
440 %************************************************************************
441
442 If this Id has a worker then we store a reference to it. Worker
443 functions are generated by the worker/wrapper pass.  This uses
444 information from the strictness and CPR analyses.
445
446 There might not be a worker, even for a strict function, because:
447 (a) the function might be small enough to inline, so no need 
448     for w/w split
449 (b) the strictness info might be "SSS" or something, so no w/w split.
450
451 \begin{code}
452
453 type WorkerInfo = Maybe Id
454
455 {- UNUSED:
456 mkWorkerInfo :: Id -> WorkerInfo
457 mkWorkerInfo wk_id = Just wk_id
458 -}
459
460 seqWorker :: WorkerInfo -> ()
461 seqWorker (Just id) = id `seq` ()
462 seqWorker Nothing   = ()
463
464 ppWorkerInfo Nothing      = empty
465 ppWorkerInfo (Just wk_id) = ptext SLIT("__P") <+> ppr wk_id
466
467 noWorkerInfo = Nothing
468
469 workerExists :: Maybe Id -> Bool
470 workerExists = isJust
471 \end{code}
472
473
474 %************************************************************************
475 %*                                                                      *
476 \subsection[update-IdInfo]{Update-analysis info about an @Id@}
477 %*                                                                      *
478 %************************************************************************
479
480 \begin{code}
481 data UpdateInfo
482   = NoUpdateInfo
483   | SomeUpdateInfo UpdateSpec
484   deriving (Eq, Ord)
485       -- we need Eq/Ord to cross-chk update infos in interfaces
486
487 -- the form in which we pass update-analysis info between modules:
488 type UpdateSpec = [Int]
489 \end{code}
490
491 \begin{code}
492 mkUpdateInfo = SomeUpdateInfo
493
494 updateInfoMaybe NoUpdateInfo        = Nothing
495 updateInfoMaybe (SomeUpdateInfo []) = Nothing
496 updateInfoMaybe (SomeUpdateInfo  u) = Just u
497 \end{code}
498
499 Text instance so that the update annotations can be read in.
500
501 \begin{code}
502 ppUpdateInfo NoUpdateInfo          = empty
503 ppUpdateInfo (SomeUpdateInfo [])   = empty
504 ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("__UA ")) (hcat (map int spec))
505   -- was "__U "; changed to avoid conflict with unfoldings.  KSW 1999-07.
506 \end{code}
507
508 %************************************************************************
509 %*                                                                      *
510 \subsection[CAF-IdInfo]{CAF-related information}
511 %*                                                                      *
512 %************************************************************************
513
514 This information is used to build Static Reference Tables (see
515 simplStg/ComputeSRT.lhs).
516
517 \begin{code}
518 data CafInfo 
519         = MayHaveCafRefs                -- either:
520                                         -- (1) A function or static constructor
521                                         --     that refers to one or more CAFs,
522                                         -- (2) A real live CAF
523
524         | NoCafRefs                     -- A function or static constructor
525                                         -- that refers to no CAFs.
526
527 -- LATER: not sure how easy this is...
528 --      | OneCafRef Id
529
530
531 seqCaf c = c `seq` ()
532
533 ppCafInfo NoCafRefs = ptext SLIT("__C")
534 ppCafInfo MayHaveCafRefs = empty
535 \end{code}
536
537
538 %************************************************************************
539 %*                                                                      *
540 \subsection[CAF-IdInfo]{CAF-related information}
541 %*                                                                      *
542 %************************************************************************
543
544 zapFragileIdInfo is used when cloning binders, mainly in the
545 simplifier.  We must forget about used-once information because that
546 isn't necessarily correct in the transformed program.
547 Also forget specialisations and unfoldings because they would need
548 substitution to be correct.  (They get pinned back on separately.)
549
550 \begin{code}
551 zapFragileIdInfo :: IdInfo -> Maybe IdInfo
552 zapFragileIdInfo info@(IdInfo {inlinePragInfo   = inline_prag, 
553                                workerInfo       = wrkr,
554                                specInfo         = rules, 
555                                unfoldingInfo    = unfolding})
556   |  not is_fragile_inline_prag 
557         -- We must forget about whether it was marked safe-to-inline,
558         -- because that isn't necessarily true in the simplified expression.
559         -- This is important because expressions may  be re-simplified
560
561   && isEmptyCoreRules rules
562         -- Specialisations would need substituting.  They get pinned
563         -- back on separately.
564
565   && not (workerExists wrkr)
566
567   && not (hasUnfolding unfolding)
568         -- This is very important; occasionally a let-bound binder is used
569         -- as a binder in some lambda, in which case its unfolding is utterly
570         -- bogus.  Also the unfolding uses old binders so if we left it we'd
571         -- have to substitute it. Much better simply to give the Id a new
572         -- unfolding each time, which is what the simplifier does.
573   = Nothing
574
575   | otherwise
576   = Just (info {inlinePragInfo  = safe_inline_prag, 
577                 workerInfo      = noWorkerInfo,
578                 specInfo        = emptyCoreRules,
579                 unfoldingInfo   = noUnfolding})
580
581   where
582     is_fragile_inline_prag = case inline_prag of
583                                 ICanSafelyBeINLINEd _ _ -> True
584
585 -- We used to say the dead-ness was fragile, but I don't
586 -- see why it is.  Furthermore, deadness is a pain to lose;
587 -- see Simplify.mkDupableCont (Select ...)
588 --                              IAmDead                 -> True
589
590                                 other                   -> False
591
592         -- Be careful not to destroy real 'pragma' info
593     safe_inline_prag | is_fragile_inline_prag = NoInlinePragInfo
594                      | otherwise              = inline_prag
595 \end{code}
596
597
598 @zapLamIdInfo@ is used for lambda binders that turn out to to be
599 part of an unsaturated lambda
600
601 \begin{code}
602 zapLamIdInfo :: IdInfo -> Maybe IdInfo
603 zapLamIdInfo info@(IdInfo {inlinePragInfo = inline_prag, demandInfo = demand})
604   | is_safe_inline_prag && not (isStrict demand)
605   = Nothing
606   | otherwise
607   = Just (info {inlinePragInfo = safe_inline_prag,
608                 demandInfo = wwLazy})
609   where
610         -- The "unsafe" prags are the ones that say I'm not in a lambda
611         -- because that might not be true for an unsaturated lambda
612     is_safe_inline_prag = case inline_prag of
613                                 ICanSafelyBeINLINEd NotInsideLam nalts -> False
614                                 other                                  -> True
615
616     safe_inline_prag    = case inline_prag of
617                                 ICanSafelyBeINLINEd _ nalts
618                                       -> ICanSafelyBeINLINEd InsideLam nalts
619                                 other -> inline_prag
620 \end{code}
621
622 \begin{code}
623 zapIdInfoForStg :: IdInfo -> IdInfo
624         -- Return only the info needed for STG stuff
625         -- Namely, nothing, I think
626 zapIdInfoForStg info = vanillaIdInfo    
627 \end{code}
628
629
630 %************************************************************************
631 %*                                                                      *
632 \subsection[cpr-IdInfo]{Constructed Product Result info about an @Id@}
633 %*                                                                      *
634 %************************************************************************
635
636 If the @Id@ is a function then it may have CPR info. A CPR analysis
637 phase detects whether:
638
639 \begin{enumerate}
640 \item
641 The function's return value has a product type, i.e. an algebraic  type 
642 with a single constructor. Examples of such types are tuples and boxed
643 primitive values.
644 \item
645 The function always 'constructs' the value that it is returning.  It
646 must do this on every path through,  and it's OK if it calls another
647 function which constructs the result.
648 \end{enumerate}
649
650 If this is the case then we store a template which tells us the
651 function has the CPR property and which components of the result are
652 also CPRs.   
653
654 \begin{code}
655 data CprInfo
656   = NoCPRInfo
657
658   | CPRInfo [CprInfo] 
659
660 -- e.g. const 5 == CPRInfo [NoCPRInfo]
661 --              == __M(-)
662 --      \x -> (5,
663 --              (x,
664 --               5,
665 --               x)
666 --            ) 
667 --            CPRInfo [CPRInfo [NoCPRInfo], 
668 --                     CPRInfo [NoCprInfo,
669 --                              CPRInfo [NoCPRInfo],
670 --                              NoCPRInfo]
671 --                    ]
672 --            __M((-)(-(-)-)-)
673 \end{code}
674
675 \begin{code}
676 seqCpr :: CprInfo -> ()
677 seqCpr (CPRInfo cs) = seqCprs cs
678 seqCpr NoCPRInfo    = ()
679
680 seqCprs [] = ()
681 seqCprs (c:cs) = seqCpr c `seq` seqCprs cs
682
683
684 noCprInfo       = NoCPRInfo
685
686 ppCprInfo NoCPRInfo = empty
687 ppCprInfo c@(CPRInfo _)
688   = hsep [ptext SLIT("__M"), ppCprInfo' c]
689     where
690     ppCprInfo' NoCPRInfo      = char '-'
691     ppCprInfo' (CPRInfo args) = parens (hcat (map ppCprInfo' args))
692
693 instance Outputable CprInfo where
694     ppr = ppCprInfo
695
696 instance Show CprInfo where
697     showsPrec p c = showsPrecSDoc p (ppr c)
698 \end{code}
699
700
701 %************************************************************************
702 %*                                                                      *
703 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
704 %*                                                                      *
705 %************************************************************************
706
707 If the @Id@ is a lambda-bound variable then it may have lambda-bound
708 var info.  The usage analysis (UsageSP) detects whether the lambda
709 binding this var is a ``one-shot'' lambda; that is, whether it is
710 applied at most once.
711
712 This information may be useful in optimisation, as computations may
713 safely be floated inside such a lambda without risk of duplicating
714 work.
715
716 \begin{code}
717 data LBVarInfo
718   = NoLBVarInfo
719
720   | IsOneShotLambda             -- The lambda that binds this Id is applied
721                                 --   at most once
722                                 -- HACK ALERT! placing this info here is a short-term hack,
723                                 --   but it minimises changes to the rest of the compiler.
724                                 --   Hack agreed by SLPJ/KSW 1999-04.
725
726 seqLBVar l = l `seq` ()
727 \end{code}
728
729 \begin{code}
730 noLBVarInfo = NoLBVarInfo
731
732 -- not safe to print or parse LBVarInfo because it is not really a
733 -- property of the definition, but a property of the context.
734 pprLBVarInfo NoLBVarInfo     = empty
735 pprLBVarInfo IsOneShotLambda = getPprStyle $ \ sty ->
736                                if ifaceStyle sty then empty
737                                                  else ptext SLIT("OneShot")
738
739 instance Outputable LBVarInfo where
740     ppr = pprLBVarInfo
741
742 instance Show LBVarInfo where
743     showsPrec p c = showsPrecSDoc p (ppr c)
744 \end{code}