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