[project @ 1998-12-02 13:17:09 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, mkBottomStrictnessInfo, 
24         noStrictnessInfo, bottomIsGuaranteed, strictnessInfo, 
25         ppStrictnessInfo, setStrictnessInfo, 
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 \begin{code}
113 ppIdInfo :: IdInfo -> SDoc
114 ppIdInfo (IdInfo {arityInfo, 
115                   demandInfo,
116                   specInfo,
117                   strictnessInfo, 
118                   unfoldingInfo,
119                   updateInfo, 
120                   cafInfo,
121                   inlinePragInfo})
122   = hsep [
123             ppArityInfo arityInfo,
124             ppUpdateInfo updateInfo,
125             ppStrictnessInfo strictnessInfo,
126             ppr demandInfo,
127             ppCafInfo cafInfo
128         -- Inline pragma printed out with all binders; see PprCore.pprIdBndr
129         ]
130 \end{code}
131
132 %************************************************************************
133 %*                                                                      *
134 \subsection[arity-IdInfo]{Arity info about an @Id@}
135 %*                                                                      *
136 %************************************************************************
137
138 For locally-defined Ids, the code generator maintains its own notion
139 of their arities; so it should not be asking...  (but other things
140 besides the code-generator need arity info!)
141
142 \begin{code}
143 data ArityInfo
144   = UnknownArity        -- No idea
145   | ArityExactly Int    -- Arity is exactly this
146   | ArityAtLeast Int    -- Arity is this or greater
147
148 exactArity   = ArityExactly
149 atLeastArity = ArityAtLeast
150 unknownArity = UnknownArity
151
152 arityLowerBound :: ArityInfo -> Int
153 arityLowerBound UnknownArity     = 0
154 arityLowerBound (ArityAtLeast n) = n
155 arityLowerBound (ArityExactly n) = n
156
157
158 ppArityInfo UnknownArity         = empty
159 ppArityInfo (ArityExactly arity) = hsep [ptext SLIT("__A"), int arity]
160 ppArityInfo (ArityAtLeast arity) = hsep [ptext SLIT("__AL"), int arity]
161 \end{code}
162
163 %************************************************************************
164 %*                                                                      *
165 \subsection{Inline-pragma information}
166 %*                                                                      *
167 %************************************************************************
168
169 \begin{code}
170 data InlinePragInfo
171   = NoInlinePragInfo
172
173   | IAmASpecPragmaId    -- Used for spec-pragma Ids; don't discard or inline
174
175   | IWantToBeINLINEd    -- User INLINE pragma
176   | IMustNotBeINLINEd   -- User NOINLINE pragma
177
178   | IAmALoopBreaker     -- Used by the occurrence analyser to mark loop-breakers
179                         -- in a group of recursive definitions
180
181   | ICanSafelyBeINLINEd -- Used by the occurrence analyser to mark things
182                         -- that manifesly occur once, not inside SCCs, 
183                         -- not in constructor arguments
184
185         OccInfo         -- Says whether the occurrence is inside a lambda
186                         --      If so, must only substitute WHNFs
187
188         Bool            -- False <=> occurs in more than one case branch
189                         --      If so, there's a code-duplication issue
190
191   | IAmDead             -- Marks unused variables.  Sometimes useful for
192                         -- lambda and case-bound variables.
193
194   | IMustBeINLINEd      -- Absolutely must inline; used for PrimOps and
195                         -- constructors only.
196
197 instance Outputable InlinePragInfo where
198   ppr NoInlinePragInfo          = empty
199   ppr IMustBeINLINEd            = ptext SLIT("__UU")
200   ppr IWantToBeINLINEd          = ptext SLIT("__U")
201   ppr IMustNotBeINLINEd         = ptext SLIT("__Unot")
202   ppr IAmALoopBreaker           = ptext SLIT("__Ux")
203   ppr IAmDead                   = ptext SLIT("__Ud")
204   ppr (ICanSafelyBeINLINEd _ _) = ptext SLIT("__Us")
205   ppr IAmASpecPragmaId          = ptext SLIT("__US")
206
207 instance Show InlinePragInfo where
208   showsPrec p prag = showsPrecSDoc p (ppr prag)
209 \end{code}
210
211 The @IMustNotBeDiscarded@ exists only to make Ids that are
212 on the *LHS* of bindings created by SPECIALISE pragmas; 
213 eg:             s = f Int d
214 The SpecPragmaId is never itself mentioned; it
215 exists solely so that the specialiser will find
216 the call to f, and make specialised version of it.
217 The SpecPragmaId binding is discarded by the specialiser
218 when it gathers up overloaded calls.
219 Meanwhile, it is not discarded as dead code.
220
221 \begin{code}
222 data OccInfo
223   = StrictOcc           -- Occurs syntactically strictly;
224                         -- i.e. in a function position or case scrutinee
225
226   | LazyOcc             -- Not syntactically strict (*even* that of a strict function)
227                         -- or in a case branch where there's more than one alternative
228
229   | InsideLam           -- Inside a non-linear lambda (that is, a lambda which
230                         -- is sure to be instantiated only once).
231                         -- Substituting a redex for this occurrence is
232                         -- dangerous because it might duplicate work.
233
234 instance Outputable OccInfo where
235   ppr StrictOcc = text "s"
236   ppr LazyOcc   = empty
237   ppr InsideLam = text "l"
238
239
240 notInsideLambda :: OccInfo -> Bool
241 notInsideLambda StrictOcc = True
242 notInsideLambda LazyOcc   = True
243 notInsideLambda InsideLam = False
244 \end{code}
245
246 %************************************************************************
247 %*                                                                      *
248 \subsection[specialisation-IdInfo]{Specialisation info about an @Id@}
249 %*                                                                      *
250 %************************************************************************
251
252 A @IdSpecEnv@ holds details of an @Id@'s specialisations. 
253
254 \begin{code}
255 type IdSpecEnv = SpecEnv CoreExpr
256 \end{code}
257
258 For example, if \tr{f}'s @SpecEnv@ contains the mapping:
259 \begin{verbatim}
260         [List a, b]  ===>  (\d -> f' a b)
261 \end{verbatim}
262 then when we find an application of f to matching types, we simply replace
263 it by the matching RHS:
264 \begin{verbatim}
265         f (List Int) Bool ===>  (\d -> f' Int Bool)
266 \end{verbatim}
267 All the stuff about how many dictionaries to discard, and what types
268 to apply the specialised function to, are handled by the fact that the
269 SpecEnv contains a template for the result of the specialisation.
270
271 There is one more exciting case, which is dealt with in exactly the same
272 way.  If the specialised value is unboxed then it is lifted at its
273 definition site and unlifted at its uses.  For example:
274
275         pi :: forall a. Num a => a
276
277 might have a specialisation
278
279         [Int#] ===>  (case pi' of Lift pi# -> pi#)
280
281 where pi' :: Lift Int# is the specialised version of pi.
282
283
284
285 %************************************************************************
286 %*                                                                      *
287 \subsection[strictness-IdInfo]{Strictness info about an @Id@}
288 %*                                                                      *
289 %************************************************************************
290
291 We specify the strictness of a function by giving information about
292 each of the ``wrapper's'' arguments (see the description about
293 worker/wrapper-style transformations in the PJ/Launchbury paper on
294 unboxed types).
295
296 The list of @Demands@ specifies: (a)~the strictness properties
297 of a function's arguments; (b)~the {\em existence} of a ``worker''
298 version of the function; and (c)~the type signature of that worker (if
299 it exists); i.e. its calling convention.
300
301 \begin{code}
302 data StrictnessInfo
303   = NoStrictnessInfo
304
305   | BottomGuaranteed    -- This Id guarantees never to return;
306                         -- it is bottom regardless of its arguments.
307                         -- Useful for "error" and other disguised
308                         -- variants thereof.
309
310   | StrictnessInfo [Demand] 
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
317                                 -- Worker's Id, if applicable, and a list of the constructors
318                                 -- mentioned by the wrapper.  This is necessary so that the
319                                 -- renamer can slurp them in.  Without this info, the renamer doesn't
320                                 -- know which data types to slurp in concretely.  Remember, for
321                                 -- strict things we don't put the unfolding in the interface file, to save space.
322                                 -- This constructor list allows the renamer to behave much as if the
323                                 -- unfolding *was* in the interface file.
324 \end{code}
325
326 \begin{code}
327 mkStrictnessInfo :: [Demand] -> Bool -> StrictnessInfo
328
329 mkStrictnessInfo xs has_wrkr
330   | all isLazy xs        = NoStrictnessInfo             -- Uninteresting
331   | otherwise            = StrictnessInfo xs has_wrkr
332
333 noStrictnessInfo       = NoStrictnessInfo
334 mkBottomStrictnessInfo = BottomGuaranteed
335
336 bottomIsGuaranteed BottomGuaranteed = True
337 bottomIsGuaranteed other            = False
338
339 ppStrictnessInfo NoStrictnessInfo = empty
340 ppStrictnessInfo BottomGuaranteed = ptext SLIT("__bot")
341
342 ppStrictnessInfo (StrictnessInfo wrapper_args wrkr_maybe)
343   = hsep [ptext SLIT("__S"), pprDemands wrapper_args]
344 \end{code}
345
346
347 \begin{code}
348 workerExists :: StrictnessInfo -> Bool
349 workerExists (StrictnessInfo _ worker_exists) = worker_exists
350 workerExists other                            = False
351 \end{code}
352
353
354 %************************************************************************
355 %*                                                                      *
356 \subsection[update-IdInfo]{Update-analysis info about an @Id@}
357 %*                                                                      *
358 %************************************************************************
359
360 \begin{code}
361 data UpdateInfo
362   = NoUpdateInfo
363   | SomeUpdateInfo UpdateSpec
364   deriving (Eq, Ord)
365       -- we need Eq/Ord to cross-chk update infos in interfaces
366
367 -- the form in which we pass update-analysis info between modules:
368 type UpdateSpec = [Int]
369 \end{code}
370
371 \begin{code}
372 mkUpdateInfo = SomeUpdateInfo
373
374 updateInfoMaybe NoUpdateInfo        = Nothing
375 updateInfoMaybe (SomeUpdateInfo []) = Nothing
376 updateInfoMaybe (SomeUpdateInfo  u) = Just u
377 \end{code}
378
379 Text instance so that the update annotations can be read in.
380
381 \begin{code}
382 ppUpdateInfo NoUpdateInfo          = empty
383 ppUpdateInfo (SomeUpdateInfo [])   = empty
384 ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("__U ")) (hcat (map int spec))
385 \end{code}
386
387 %************************************************************************
388 %*                                                                      *
389 \subsection[CAF-IdInfo]{CAF-related information}
390 %*                                                                      *
391 %************************************************************************
392
393 This information is used to build Static Reference Tables (see
394 simplStg/ComputeSRT.lhs).
395
396 \begin{code}
397 data CafInfo 
398         = MayHaveCafRefs                -- either:
399                                         -- (1) A function or static constructor
400                                         --     that refers to one or more CAFs,
401                                         -- (2) A real live CAF
402
403         | NoCafRefs                     -- A function or static constructor
404                                         -- that refers to no CAFs.
405
406 -- LATER: not sure how easy this is...
407 --      | OneCafRef Id
408
409
410 ppCafInfo NoCafRefs = ptext SLIT("__C")
411 ppCafInfo MayHaveCafRefs = empty
412 \end{code}