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