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