[project @ 1999-05-11 16:42:54 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         noIdInfo,
14
15         -- Arity
16         ArityInfo(..),
17         exactArity, atLeastArity, unknownArity,
18         arityInfo, setArityInfo, ppArityInfo, arityLowerBound,
19
20         -- Strictness
21         StrictnessInfo(..),                             -- Non-abstract
22         mkStrictnessInfo,
23         noStrictnessInfo, strictnessInfo,
24         ppStrictnessInfo, setStrictnessInfo, 
25         isBottomingStrictness, appIsBottom,
26
27         -- Worker
28         WorkerInfo, workerExists, 
29         workerInfo, setWorkerInfo,
30
31         -- Unfolding
32         unfoldingInfo, setUnfoldingInfo, 
33
34         -- DemandInfo
35         demandInfo, setDemandInfo, 
36
37         -- Inline prags
38         InlinePragInfo(..), OccInfo(..),
39         inlinePragInfo, setInlinePragInfo, notInsideLambda,
40
41         -- Specialisation
42         IdSpecEnv, specInfo, setSpecInfo,
43
44         -- Update
45         UpdateInfo, UpdateSpec,
46         mkUpdateInfo, updateInfo, updateInfoMaybe, ppUpdateInfo, setUpdateInfo,
47
48         -- CAF info
49         CafInfo(..), cafInfo, setCafInfo, ppCafInfo,
50
51         -- Constructed Product Result Info
52         CprInfo(..), cprInfo, setCprInfo, ppCprInfo, noCprInfo,
53
54         -- Lambda-bound variable info
55         LBVarInfo(..), lbvarInfo, setLBVarInfo, noLBVarInfo,
56     ) where
57
58 #include "HsVersions.h"
59
60
61 import {-# SOURCE #-} CoreUnfold ( Unfolding, noUnfolding )
62 import {-# SOURCE #-} CoreSyn    ( CoreExpr )
63
64 import Var              ( Id )
65 import SpecEnv          ( SpecEnv, emptySpecEnv )
66 import Demand           ( Demand,  isLazy, wwLazy, pprDemands )
67 import Type             ( UsageAnn )
68 import Outputable       
69
70 import Maybe            ( isJust )
71
72 \end{code}
73
74 An @IdInfo@ gives {\em optional} information about an @Id@.  If
75 present it never lies, but it may not be present, in which case there
76 is always a conservative assumption which can be made.
77
78 Two @Id@s may have different info even though they have the same
79 @Unique@ (and are hence the same @Id@); for example, one might lack
80 the properties attached to the other.
81
82 The @IdInfo@ gives information about the value, or definition, of the
83 @Id@.  It does {\em not} contain information about the @Id@'s usage
84 (except for @DemandInfo@? ToDo). (@lbvarInfo@ is also a marginal
85 case.  KSW 1999-04).
86
87 \begin{code}
88 data IdInfo
89   = IdInfo {
90         arityInfo :: ArityInfo,                 -- Its arity
91         demandInfo :: Demand,                   -- Whether or not it is definitely demanded
92         specInfo :: IdSpecEnv,                  -- Specialisations of this function which exist
93         strictnessInfo :: StrictnessInfo,       -- Strictness properties
94         workerInfo :: WorkerInfo,               -- Pointer to Worker Function
95         unfoldingInfo :: Unfolding,             -- Its unfolding
96         updateInfo :: UpdateInfo,               -- Which args should be updated
97         cafInfo :: CafInfo,
98         cprInfo :: CprInfo,                     -- Function always constructs a product result
99         lbvarInfo :: LBVarInfo,                 -- Info about a lambda-bound variable
100         inlinePragInfo :: !InlinePragInfo       -- Inline pragmas
101     }
102 \end{code}
103
104 Setters
105
106 \begin{code}
107 setUpdateInfo     ud info = info { updateInfo = ud }
108 setDemandInfo     dd info = info { demandInfo = dd }
109 setStrictnessInfo st info = info { strictnessInfo = st }
110 setWorkerInfo     wk info = info { workerInfo = wk }
111 setSpecInfo       sp info = info { specInfo = sp }
112 setArityInfo      ar info = info { arityInfo = ar  }
113 setInlinePragInfo pr info = info { inlinePragInfo = pr }
114 setUnfoldingInfo  uf info = info { unfoldingInfo = uf }
115 setCafInfo        cf info = info { cafInfo = cf }
116 setCprInfo        cp info = info { cprInfo = cp }
117 setLBVarInfo      lb info = info { lbvarInfo = lb }
118 \end{code}
119
120
121 \begin{code}
122 noIdInfo = IdInfo {
123                 arityInfo       = UnknownArity,
124                 demandInfo      = wwLazy,
125                 specInfo        = emptySpecEnv,
126                 strictnessInfo  = NoStrictnessInfo,
127                 workerInfo      = noWorkerInfo,
128                 unfoldingInfo   = noUnfolding,
129                 updateInfo      = NoUpdateInfo,
130                 cafInfo         = MayHaveCafRefs,
131                 cprInfo         = NoCPRInfo,
132                 lbvarInfo       = NoLBVarInfo,
133                 inlinePragInfo  = NoInlinePragInfo
134            }
135 \end{code}
136
137 %************************************************************************
138 %*                                                                      *
139 \subsection[arity-IdInfo]{Arity info about an @Id@}
140 %*                                                                      *
141 %************************************************************************
142
143 For locally-defined Ids, the code generator maintains its own notion
144 of their arities; so it should not be asking...  (but other things
145 besides the code-generator need arity info!)
146
147 \begin{code}
148 data ArityInfo
149   = UnknownArity        -- No idea
150   | ArityExactly Int    -- Arity is exactly this
151   | ArityAtLeast Int    -- Arity is this or greater
152
153 exactArity   = ArityExactly
154 atLeastArity = ArityAtLeast
155 unknownArity = UnknownArity
156
157 arityLowerBound :: ArityInfo -> Int
158 arityLowerBound UnknownArity     = 0
159 arityLowerBound (ArityAtLeast n) = n
160 arityLowerBound (ArityExactly n) = n
161
162
163 ppArityInfo UnknownArity         = empty
164 ppArityInfo (ArityExactly arity) = hsep [ptext SLIT("__A"), int arity]
165 ppArityInfo (ArityAtLeast arity) = hsep [ptext SLIT("__AL"), int arity]
166 \end{code}
167
168 %************************************************************************
169 %*                                                                      *
170 \subsection{Inline-pragma information}
171 %*                                                                      *
172 %************************************************************************
173
174 \begin{code}
175 data InlinePragInfo
176   = NoInlinePragInfo
177
178   | IAmASpecPragmaId    -- Used for spec-pragma Ids; don't discard or inline
179
180   | IWantToBeINLINEd    -- User INLINE pragma
181   | IMustNotBeINLINEd   -- User NOINLINE pragma
182
183   | IAmALoopBreaker     -- Used by the occurrence analyser to mark loop-breakers
184                         -- in a group of recursive definitions
185
186   | ICanSafelyBeINLINEd -- Used by the occurrence analyser to mark things
187                         -- that manifesly occur once, not inside SCCs, 
188                         -- not in constructor arguments
189
190         OccInfo         -- Says whether the occurrence is inside a lambda
191                         --      If so, must only substitute WHNFs
192
193         Bool            -- False <=> occurs in more than one case branch
194                         --      If so, there's a code-duplication issue
195
196   | IAmDead             -- Marks unused variables.  Sometimes useful for
197                         -- lambda and case-bound variables.
198
199   | IMustBeINLINEd      -- Absolutely must inline; used for PrimOps and
200                         -- constructors only.
201
202 instance Outputable InlinePragInfo where
203   ppr NoInlinePragInfo          = empty
204   ppr IMustBeINLINEd            = ptext SLIT("__UU")
205   ppr IWantToBeINLINEd          = ptext SLIT("__U")
206   ppr IMustNotBeINLINEd         = ptext SLIT("__Unot")
207   ppr IAmALoopBreaker           = ptext SLIT("__Ux")
208   ppr IAmDead                   = ptext SLIT("__Ud")
209   ppr (ICanSafelyBeINLINEd InsideLam _) = ptext SLIT("__Ul")
210   ppr (ICanSafelyBeINLINEd _ _) = ptext SLIT("__Us")
211   ppr IAmASpecPragmaId          = ptext SLIT("__US")
212
213 instance Show InlinePragInfo where
214   showsPrec p prag = showsPrecSDoc p (ppr prag)
215 \end{code}
216
217 The @IMustNotBeDiscarded@ exists only to make Ids that are
218 on the *LHS* of bindings created by SPECIALISE pragmas; 
219 eg:             s = f Int d
220 The SpecPragmaId is never itself mentioned; it
221 exists solely so that the specialiser will find
222 the call to f, and make specialised version of it.
223 The SpecPragmaId binding is discarded by the specialiser
224 when it gathers up overloaded calls.
225 Meanwhile, it is not discarded as dead code.
226
227 \begin{code}
228 data OccInfo
229   = StrictOcc           -- Occurs syntactically strictly;
230                         -- i.e. in a function position or case scrutinee
231
232   | LazyOcc             -- Not syntactically strict (*even* that of a strict function)
233                         -- or in a case branch where there's more than one alternative
234
235   | InsideLam           -- Inside a non-linear lambda (that is, a lambda which
236                         -- is sure to be instantiated only once).
237                         -- Substituting a redex for this occurrence is
238                         -- dangerous because it might duplicate work.
239
240 instance Outputable OccInfo where
241   ppr StrictOcc = text "s"
242   ppr LazyOcc   = empty
243   ppr InsideLam = text "l"
244
245
246 notInsideLambda :: OccInfo -> Bool
247 notInsideLambda StrictOcc = True
248 notInsideLambda LazyOcc   = True
249 notInsideLambda InsideLam = False
250 \end{code}
251
252 %************************************************************************
253 %*                                                                      *
254 \subsection[specialisation-IdInfo]{Specialisation info about an @Id@}
255 %*                                                                      *
256 %************************************************************************
257
258 A @IdSpecEnv@ holds details of an @Id@'s specialisations. 
259
260 \begin{code}
261 type IdSpecEnv = SpecEnv CoreExpr
262 \end{code}
263
264 For example, if \tr{f}'s @SpecEnv@ contains the mapping:
265 \begin{verbatim}
266         [List a, b]  ===>  (\d -> f' a b)
267 \end{verbatim}
268 then when we find an application of f to matching types, we simply replace
269 it by the matching RHS:
270 \begin{verbatim}
271         f (List Int) Bool ===>  (\d -> f' Int Bool)
272 \end{verbatim}
273 All the stuff about how many dictionaries to discard, and what types
274 to apply the specialised function to, are handled by the fact that the
275 SpecEnv contains a template for the result of the specialisation.
276
277 There is one more exciting case, which is dealt with in exactly the same
278 way.  If the specialised value is unboxed then it is lifted at its
279 definition site and unlifted at its uses.  For example:
280
281         pi :: forall a. Num a => a
282
283 might have a specialisation
284
285         [Int#] ===>  (case pi' of Lift pi# -> pi#)
286
287 where pi' :: Lift Int# is the specialised version of pi.
288
289
290 %************************************************************************
291 %*                                                                      *
292 \subsection[strictness-IdInfo]{Strictness info about an @Id@}
293 %*                                                                      *
294 %************************************************************************
295
296 We specify the strictness of a function by giving information about
297 each of the ``wrapper's'' arguments (see the description about
298 worker/wrapper-style transformations in the PJ/Launchbury paper on
299 unboxed types).
300
301 The list of @Demands@ specifies: (a)~the strictness properties of a
302 function's arguments; and (b)~the type signature of that worker (if it
303 exists); i.e. its calling convention.
304
305 Note that the existence of a worker function is now denoted by the Id's
306 workerInfo field.
307
308 \begin{code}
309 data StrictnessInfo
310   = NoStrictnessInfo
311
312   | StrictnessInfo [Demand] 
313                    Bool         -- True <=> the function diverges regardless of its arguments
314                                 -- Useful for "error" and other disguised variants thereof.  
315                                 -- BUT NB: f = \x y. error "urk"
316                                 --         will have info  SI [SS] True
317                                 -- but still (f) and (f 2) are not bot; only (f 3 2) is bot
318 \end{code}
319
320 \begin{code}
321 mkStrictnessInfo :: ([Demand], Bool) -> StrictnessInfo
322
323 mkStrictnessInfo (xs, is_bot)
324   | all isLazy xs && not is_bot = NoStrictnessInfo              -- Uninteresting
325   | otherwise                   = StrictnessInfo xs is_bot
326
327 noStrictnessInfo       = NoStrictnessInfo
328
329 isBottomingStrictness (StrictnessInfo _ bot) = bot
330 isBottomingStrictness NoStrictnessInfo       = False
331
332 -- appIsBottom returns true if an application to n args would diverge
333 appIsBottom (StrictnessInfo ds bot)   n = bot && (n >= length ds)
334 appIsBottom  NoStrictnessInfo         n = False
335
336 ppStrictnessInfo NoStrictnessInfo = empty
337 ppStrictnessInfo (StrictnessInfo wrapper_args bot)
338   = hsep [ptext SLIT("__S"), pprDemands wrapper_args bot]
339 \end{code}
340
341 %************************************************************************
342 %*                                                                      *
343 \subsection[worker-IdInfo]{Worker info about an @Id@}
344 %*                                                                      *
345 %************************************************************************
346
347 If this Id has a worker then we store a reference to it. Worker
348 functions are generated by the worker/wrapper pass.  This uses
349 information from the strictness and CPR analyses.
350
351 There might not be a worker, even for a strict function, because:
352 (a) the function might be small enough to inline, so no need 
353     for w/w split
354 (b) the strictness info might be "SSS" or something, so no w/w split.
355
356 \begin{code}
357
358 type WorkerInfo = Maybe Id
359
360 {- UNUSED:
361 mkWorkerInfo :: Id -> WorkerInfo
362 mkWorkerInfo wk_id = Just wk_id
363
364 ppWorkerInfo Nothing      = empty
365 ppWorkerInfo (Just wk_id) = ppr wk_id
366 -}
367
368 noWorkerInfo = Nothing
369
370 workerExists :: Maybe Id -> Bool
371 workerExists = isJust
372 \end{code}
373
374
375 %************************************************************************
376 %*                                                                      *
377 \subsection[update-IdInfo]{Update-analysis info about an @Id@}
378 %*                                                                      *
379 %************************************************************************
380
381 \begin{code}
382 data UpdateInfo
383   = NoUpdateInfo
384   | SomeUpdateInfo UpdateSpec
385   deriving (Eq, Ord)
386       -- we need Eq/Ord to cross-chk update infos in interfaces
387
388 -- the form in which we pass update-analysis info between modules:
389 type UpdateSpec = [Int]
390 \end{code}
391
392 \begin{code}
393 mkUpdateInfo = SomeUpdateInfo
394
395 updateInfoMaybe NoUpdateInfo        = Nothing
396 updateInfoMaybe (SomeUpdateInfo []) = Nothing
397 updateInfoMaybe (SomeUpdateInfo  u) = Just u
398 \end{code}
399
400 Text instance so that the update annotations can be read in.
401
402 \begin{code}
403 ppUpdateInfo NoUpdateInfo          = empty
404 ppUpdateInfo (SomeUpdateInfo [])   = empty
405 ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("__U ")) (hcat (map int spec))
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 ppCafInfo NoCafRefs = ptext SLIT("__C")
432 ppCafInfo MayHaveCafRefs = empty
433 \end{code}
434
435 %************************************************************************
436 %*                                                                      *
437 \subsection[cpr-IdInfo]{Constructed Product Result info about an @Id@}
438 %*                                                                      *
439 %************************************************************************
440
441 If the @Id@ is a function then it may have CPR info. A CPR analysis
442 phase detects whether:
443
444 \begin{enumerate}
445 \item
446 The function's return value has a product type, i.e. an algebraic  type 
447 with a single constructor. Examples of such types are tuples and boxed
448 primitive values.
449 \item
450 The function always 'constructs' the value that it is returning.  It
451 must do this on every path through,  and it's OK if it calls another
452 function which constructs the result.
453 \end{enumerate}
454
455 If this is the case then we store a template which tells us the
456 function has the CPR property and which components of the result are
457 also CPRs.   
458
459 \begin{code}
460 data CprInfo
461   = NoCPRInfo
462
463   | CPRInfo [CprInfo] 
464
465 -- e.g. const 5 == CPRInfo [NoCPRInfo]
466 --              == __M(-)
467 --      \x -> (5,
468 --              (x,
469 --               5,
470 --               x)
471 --            ) 
472 --            CPRInfo [CPRInfo [NoCPRInfo], 
473 --                     CPRInfo [NoCprInfo,
474 --                              CPRInfo [NoCPRInfo],
475 --                              NoCPRInfo]
476 --                    ]
477 --            __M((-)(-(-)-)-)
478 \end{code}
479
480 \begin{code}
481
482 noCprInfo       = NoCPRInfo
483
484 ppCprInfo NoCPRInfo = empty
485 ppCprInfo c@(CPRInfo _)
486   = hsep [ptext SLIT("__M"), ppCprInfo' c]
487     where
488     ppCprInfo' NoCPRInfo      = char '-'
489     ppCprInfo' (CPRInfo args) = parens (hcat (map ppCprInfo' args))
490
491 instance Outputable CprInfo where
492     ppr = ppCprInfo
493
494 instance Show CprInfo where
495     showsPrec p c = showsPrecSDoc p (ppr c)
496 \end{code}
497
498
499 %************************************************************************
500 %*                                                                      *
501 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
502 %*                                                                      *
503 %************************************************************************
504
505 If the @Id@ is a lambda-bound variable then it may have lambda-bound
506 var info.  The usage analysis (UsageSP) detects whether the lambda
507 binding this var is a ``one-shot'' lambda; that is, whether it is
508 applied at most once.
509
510 This information may be useful in optimisation, as computations may
511 safely be floated inside such a lambda without risk of duplicating
512 work.
513
514 \begin{code}
515 data LBVarInfo
516   = NoLBVarInfo
517
518   | IsOneShotLambda                     -- the lambda that binds this Id is applied
519                                         --   at most once
520                                 -- HACK ALERT! placing this info here is a short-term hack,
521                                 --   but it minimises changes to the rest of the compiler.
522                                 --   Hack agreed by SLPJ/KSW 1999-04.
523 \end{code}
524
525 \begin{code}
526
527 noLBVarInfo = NoLBVarInfo
528
529 -- not safe to print or parse LBVarInfo because it is not really a
530 -- property of the definition, but a property of the context.
531 ppLBVarInfo _ = empty
532
533 instance Outputable LBVarInfo where
534     ppr = ppLBVarInfo
535
536 instance Show LBVarInfo where
537     showsPrec p c = showsPrecSDoc p (ppr c)
538 \end{code}