[project @ 1999-01-15 15:06:20 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      = a,
116                   demandInfo     = d,
117                   strictnessInfo = s,
118                   updateInfo     = u,
119                   cafInfo        = c
120                   }) 
121   = hsep [
122             ppArityInfo a,
123             ppUpdateInfo u,
124             ppStrictnessInfo s,
125             ppr d,
126             ppCafInfo c
127         -- Inline pragma printed out with all binders; see PprCore.pprIdBndr
128         ]
129 \end{code}
130
131 %************************************************************************
132 %*                                                                      *
133 \subsection[arity-IdInfo]{Arity info about an @Id@}
134 %*                                                                      *
135 %************************************************************************
136
137 For locally-defined Ids, the code generator maintains its own notion
138 of their arities; so it should not be asking...  (but other things
139 besides the code-generator need arity info!)
140
141 \begin{code}
142 data ArityInfo
143   = UnknownArity        -- No idea
144   | ArityExactly Int    -- Arity is exactly this
145   | ArityAtLeast Int    -- Arity is this or greater
146
147 exactArity   = ArityExactly
148 atLeastArity = ArityAtLeast
149 unknownArity = UnknownArity
150
151 arityLowerBound :: ArityInfo -> Int
152 arityLowerBound UnknownArity     = 0
153 arityLowerBound (ArityAtLeast n) = n
154 arityLowerBound (ArityExactly n) = n
155
156
157 ppArityInfo UnknownArity         = empty
158 ppArityInfo (ArityExactly arity) = hsep [ptext SLIT("__A"), int arity]
159 ppArityInfo (ArityAtLeast arity) = hsep [ptext SLIT("__AL"), int arity]
160 \end{code}
161
162 %************************************************************************
163 %*                                                                      *
164 \subsection{Inline-pragma information}
165 %*                                                                      *
166 %************************************************************************
167
168 \begin{code}
169 data InlinePragInfo
170   = NoInlinePragInfo
171
172   | IAmASpecPragmaId    -- Used for spec-pragma Ids; don't discard or inline
173
174   | IWantToBeINLINEd    -- User INLINE pragma
175   | IMustNotBeINLINEd   -- User NOINLINE pragma
176
177   | IAmALoopBreaker     -- Used by the occurrence analyser to mark loop-breakers
178                         -- in a group of recursive definitions
179
180   | ICanSafelyBeINLINEd -- Used by the occurrence analyser to mark things
181                         -- that manifesly occur once, not inside SCCs, 
182                         -- not in constructor arguments
183
184         OccInfo         -- Says whether the occurrence is inside a lambda
185                         --      If so, must only substitute WHNFs
186
187         Bool            -- False <=> occurs in more than one case branch
188                         --      If so, there's a code-duplication issue
189
190   | IAmDead             -- Marks unused variables.  Sometimes useful for
191                         -- lambda and case-bound variables.
192
193   | IMustBeINLINEd      -- Absolutely must inline; used for PrimOps and
194                         -- constructors only.
195
196 instance Outputable InlinePragInfo where
197   ppr NoInlinePragInfo          = empty
198   ppr IMustBeINLINEd            = ptext SLIT("__UU")
199   ppr IWantToBeINLINEd          = ptext SLIT("__U")
200   ppr IMustNotBeINLINEd         = ptext SLIT("__Unot")
201   ppr IAmALoopBreaker           = ptext SLIT("__Ux")
202   ppr IAmDead                   = ptext SLIT("__Ud")
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 %*                                                                      *
286 \subsection[strictness-IdInfo]{Strictness info about an @Id@}
287 %*                                                                      *
288 %************************************************************************
289
290 We specify the strictness of a function by giving information about
291 each of the ``wrapper's'' arguments (see the description about
292 worker/wrapper-style transformations in the PJ/Launchbury paper on
293 unboxed types).
294
295 The list of @Demands@ specifies: (a)~the strictness properties
296 of a function's arguments; (b)~the {\em existence} of a ``worker''
297 version of the function; and (c)~the type signature of that worker (if
298 it exists); i.e. its calling convention.
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
311                    Bool         -- True <=> there is a worker. There might not be, even for a
312                                 -- strict function, because:
313                                 --      (a) the function might be small enough to inline, 
314                                 --          so no need for w/w split
315                                 --      (b) the strictness info might be "SSS" or something, so no w/w split.
316 \end{code}
317
318 \begin{code}
319 mkStrictnessInfo :: ([Demand], Bool) -> Bool -> StrictnessInfo
320
321 mkStrictnessInfo (xs, is_bot) has_wrkr
322   | all isLazy xs && not is_bot = NoStrictnessInfo              -- Uninteresting
323   | otherwise                   = StrictnessInfo xs is_bot has_wrkr
324
325 noStrictnessInfo       = NoStrictnessInfo
326
327 isBottomingStrictness (StrictnessInfo _ bot _) = bot
328 isBottomingStrictness NoStrictnessInfo         = False
329
330 -- appIsBottom returns true if an application to n args would diverge
331 appIsBottom (StrictnessInfo ds bot _) n = bot && (n >= length ds)
332 appIsBottom  NoStrictnessInfo         n = False
333
334 ppStrictnessInfo NoStrictnessInfo = empty
335 ppStrictnessInfo (StrictnessInfo wrapper_args bot wrkr_maybe)
336   = hsep [ptext SLIT("__S"), pprDemands wrapper_args bot]
337 \end{code}
338
339
340 \begin{code}
341 workerExists :: StrictnessInfo -> Bool
342 workerExists (StrictnessInfo _ _ worker_exists) = worker_exists
343 workerExists other                              = False
344 \end{code}
345
346
347 %************************************************************************
348 %*                                                                      *
349 \subsection[update-IdInfo]{Update-analysis info about an @Id@}
350 %*                                                                      *
351 %************************************************************************
352
353 \begin{code}
354 data UpdateInfo
355   = NoUpdateInfo
356   | SomeUpdateInfo UpdateSpec
357   deriving (Eq, Ord)
358       -- we need Eq/Ord to cross-chk update infos in interfaces
359
360 -- the form in which we pass update-analysis info between modules:
361 type UpdateSpec = [Int]
362 \end{code}
363
364 \begin{code}
365 mkUpdateInfo = SomeUpdateInfo
366
367 updateInfoMaybe NoUpdateInfo        = Nothing
368 updateInfoMaybe (SomeUpdateInfo []) = Nothing
369 updateInfoMaybe (SomeUpdateInfo  u) = Just u
370 \end{code}
371
372 Text instance so that the update annotations can be read in.
373
374 \begin{code}
375 ppUpdateInfo NoUpdateInfo          = empty
376 ppUpdateInfo (SomeUpdateInfo [])   = empty
377 ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("__U ")) (hcat (map int spec))
378 \end{code}
379
380 %************************************************************************
381 %*                                                                      *
382 \subsection[CAF-IdInfo]{CAF-related information}
383 %*                                                                      *
384 %************************************************************************
385
386 This information is used to build Static Reference Tables (see
387 simplStg/ComputeSRT.lhs).
388
389 \begin{code}
390 data CafInfo 
391         = MayHaveCafRefs                -- either:
392                                         -- (1) A function or static constructor
393                                         --     that refers to one or more CAFs,
394                                         -- (2) A real live CAF
395
396         | NoCafRefs                     -- A function or static constructor
397                                         -- that refers to no CAFs.
398
399 -- LATER: not sure how easy this is...
400 --      | OneCafRef Id
401
402
403 ppCafInfo NoCafRefs = ptext SLIT("__C")
404 ppCafInfo MayHaveCafRefs = empty
405 \end{code}