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