[project @ 1998-03-19 23:54:49 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / IdInfo.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1996
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,
20
21         -- Demand
22         DemandInfo,
23         noDemandInfo, mkDemandInfo, demandInfo, ppDemandInfo, setDemandInfo, willBeDemanded,
24         Demand(..),                                     -- Non-abstract
25
26         -- Strictness
27         StrictnessInfo(..),                             -- Non-abstract
28         workerExists,
29         mkStrictnessInfo, mkBottomStrictnessInfo, noStrictnessInfo, bottomIsGuaranteed,
30         strictnessInfo, ppStrictnessInfo, setStrictnessInfo, 
31
32         -- Unfolding
33         unfoldingInfo, setUnfoldingInfo, 
34
35         -- Inline prags
36         InlinePragInfo(..),
37         inlinePragInfo, setInlinePragInfo,
38
39         -- Specialisation
40         IdSpecEnv, specInfo, setSpecInfo,
41
42         -- Update
43         UpdateInfo, UpdateSpec,
44         mkUpdateInfo, updateInfo, updateInfoMaybe, ppUpdateInfo, setUpdateInfo,
45
46         -- Arg usage 
47         ArgUsageInfo, ArgUsage(..), ArgUsageType,
48         mkArgUsageInfo, argUsageInfo, setArgUsageInfo, getArgUsage,
49
50         -- FB type
51         FBTypeInfo, FBType(..), FBConsum(..), FBProd(..),
52         fbTypeInfo, ppFBTypeInfo, setFBTypeInfo, mkFBTypeInfo, getFBType
53     ) where
54
55 #include "HsVersions.h"
56
57
58 import {-# SOURCE #-} CoreUnfold ( Unfolding, noUnfolding )
59 import {-# SOURCE #-} CoreSyn    ( CoreExpr )
60
61 -- for mkdependHS, CoreSyn.hi-boot refers to it:
62 import BinderInfo ( BinderInfo )
63
64 import SpecEnv          ( SpecEnv, emptySpecEnv )
65 import BasicTypes       ( NewOrData )
66
67 import Demand
68 import Outputable       
69
70 import Char             ( ord )
71 \end{code}
72
73 An @IdInfo@ gives {\em optional} information about an @Id@.  If
74 present it never lies, but it may not be present, in which case there
75 is always a conservative assumption which can be made.
76
77 Two @Id@s may have different info even though they have the same
78 @Unique@ (and are hence the same @Id@); for example, one might lack
79 the properties attached to the other.
80
81 The @IdInfo@ gives information about the value, or definition, of the
82 @Id@.  It does {\em not} contain information about the @Id@'s usage
83 (except for @DemandInfo@? ToDo).
84
85 \begin{code}
86 data IdInfo
87   = IdInfo {
88         arityInfo :: ArityInfo,                 -- Its arity
89
90         demandInfo :: DemandInfo,               -- Whether or not it is definitely demanded
91
92         specInfo :: IdSpecEnv,                  -- Specialisations of this function which exist
93
94         strictnessInfo :: StrictnessInfo,       -- Strictness properties
95
96         unfoldingInfo :: Unfolding,             -- Its unfolding; for locally-defined
97                                                 -- things, this can *only* be NoUnfolding
98
99         updateInfo :: UpdateInfo,               -- Which args should be updated
100
101         argUsageInfo :: ArgUsageInfo,           -- how this Id uses its arguments
102
103         fbTypeInfo :: FBTypeInfo,               -- the Foldr/Build W/W property of this function.
104
105         inlinePragInfo :: InlinePragInfo        -- Inline pragmas
106     }
107 \end{code}
108
109 Setters
110
111 \begin{code}
112 setFBTypeInfo     fb info = info { fbTypeInfo = fb }
113 setArgUsageInfo   au info = info { argUsageInfo = au }
114 setUpdateInfo     ud info = info { updateInfo = ud }
115 setDemandInfo     dd info = info { demandInfo = dd }
116 setStrictnessInfo st info = info { strictnessInfo = st }
117 setSpecInfo       sp info = info { specInfo = sp }
118 setArityInfo      ar info = info { arityInfo = ar  }
119 setInlinePragInfo pr info = info { inlinePragInfo = pr }
120 setUnfoldingInfo  uf info = info { unfoldingInfo = uf }
121 \end{code}
122
123
124 \begin{code}
125 noIdInfo = IdInfo {
126                 arityInfo       = UnknownArity,
127                 demandInfo      = UnknownDemand,
128                 specInfo        = emptySpecEnv,
129                 strictnessInfo  = NoStrictnessInfo,
130                 unfoldingInfo   = noUnfolding,
131                 updateInfo      = NoUpdateInfo,
132                 argUsageInfo    = NoArgUsageInfo,
133                 fbTypeInfo      = NoFBTypeInfo, 
134                 inlinePragInfo  = NoPragmaInfo
135            }
136 \end{code}
137
138 \begin{code}
139 ppIdInfo :: Bool        -- True <=> print specialisations, please
140          -> IdInfo
141          -> SDoc
142
143 ppIdInfo specs_please (IdInfo {arityInfo, updateInfo, strictnessInfo, demandInfo})
144   = hsep [
145             ppArityInfo arityInfo,
146             ppUpdateInfo updateInfo,
147             ppStrictnessInfo strictnessInfo,
148             ppDemandInfo demandInfo
149         ]
150 \end{code}
151
152 %************************************************************************
153 %*                                                                      *
154 \subsection[arity-IdInfo]{Arity info about an @Id@}
155 %*                                                                      *
156 %************************************************************************
157
158 \begin{code}
159 data ArityInfo
160   = UnknownArity        -- No idea
161   | ArityExactly Int    -- Arity is exactly this
162   | ArityAtLeast Int    -- Arity is this or greater
163
164 exactArity   = ArityExactly
165 atLeastArity = ArityAtLeast
166 unknownArity = UnknownArity
167
168 ppArityInfo UnknownArity         = empty
169 ppArityInfo (ArityExactly arity) = hsep [ptext SLIT("_A_"), int arity]
170 ppArityInfo (ArityAtLeast arity) = hsep [ptext SLIT("_A>_"), int arity]
171 \end{code}
172
173 %************************************************************************
174 %*                                                                      *
175 \subsection{Inline-pragma information}
176 %*                                                                      *
177 %************************************************************************
178
179 \begin{code}
180 data InlinePragInfo
181   = NoPragmaInfo
182
183   | IWantToBeINLINEd
184
185   | IMustNotBeINLINEd   -- Used by the simplifier to prevent looping
186                         -- on recursive definitions
187
188   | IMustBeINLINEd      -- Absolutely must inline; used for PrimOps only
189 \end{code}
190
191
192 %************************************************************************
193 %*                                                                      *
194 \subsection[specialisation-IdInfo]{Specialisation info about an @Id@}
195 %*                                                                      *
196 %************************************************************************
197
198 A @IdSpecEnv@ holds details of an @Id@'s specialisations. 
199
200 \begin{code}
201 type IdSpecEnv = SpecEnv CoreExpr
202 \end{code}
203
204 For example, if \tr{f}'s @SpecEnv@ contains the mapping:
205 \begin{verbatim}
206         [List a, b]  ===>  (\d -> f' a b)
207 \end{verbatim}
208 then when we find an application of f to matching types, we simply replace
209 it by the matching RHS:
210 \begin{verbatim}
211         f (List Int) Bool ===>  (\d -> f' Int Bool)
212 \end{verbatim}
213 All the stuff about how many dictionaries to discard, and what types
214 to apply the specialised function to, are handled by the fact that the
215 SpecEnv contains a template for the result of the specialisation.
216
217 There is one more exciting case, which is dealt with in exactly the same
218 way.  If the specialised value is unboxed then it is lifted at its
219 definition site and unlifted at its uses.  For example:
220
221         pi :: forall a. Num a => a
222
223 might have a specialisation
224
225         [Int#] ===>  (case pi' of Lift pi# -> pi#)
226
227 where pi' :: Lift Int# is the specialised version of pi.
228
229
230
231 %************************************************************************
232 %*                                                                      *
233 \subsection[strictness-IdInfo]{Strictness info about an @Id@}
234 %*                                                                      *
235 %************************************************************************
236
237 We specify the strictness of a function by giving information about
238 each of the ``wrapper's'' arguments (see the description about
239 worker/wrapper-style transformations in the PJ/Launchbury paper on
240 unboxed types).
241
242 The list of @Demands@ specifies: (a)~the strictness properties
243 of a function's arguments; (b)~the {\em existence} of a ``worker''
244 version of the function; and (c)~the type signature of that worker (if
245 it exists); i.e. its calling convention.
246
247 \begin{code}
248 data StrictnessInfo
249   = NoStrictnessInfo
250
251   | BottomGuaranteed    -- This Id guarantees never to return;
252                         -- it is bottom regardless of its arguments.
253                         -- Useful for "error" and other disguised
254                         -- variants thereof.
255
256   | StrictnessInfo [Demand] 
257                    Bool         -- True <=> there is a worker. There might not be, even for a
258                                 -- strict function, because:
259                                 --      (a) the function might be small enough to inline, 
260                                 --          so no need for w/w split
261                                 --      (b) the strictness info might be "SSS" or something, so no w/w split.
262
263                                 -- Worker's Id, if applicable, and a list of the constructors
264                                 -- mentioned by the wrapper.  This is necessary so that the
265                                 -- renamer can slurp them in.  Without this info, the renamer doesn't
266                                 -- know which data types to slurp in concretely.  Remember, for
267                                 -- strict things we don't put the unfolding in the interface file, to save space.
268                                 -- This constructor list allows the renamer to behave much as if the
269                                 -- unfolding *was* in the interface file.
270 \end{code}
271
272 \begin{code}
273 mkStrictnessInfo :: [Demand] -> Bool -> StrictnessInfo
274
275 mkStrictnessInfo xs has_wrkr
276   | all is_lazy xs       = NoStrictnessInfo             -- Uninteresting
277   | otherwise            = StrictnessInfo xs has_wrkr
278   where
279     is_lazy (WwLazy False) = True       -- NB "Absent" args do *not* count!
280     is_lazy _              = False      -- (as they imply a worker)
281
282 noStrictnessInfo       = NoStrictnessInfo
283 mkBottomStrictnessInfo = BottomGuaranteed
284
285 bottomIsGuaranteed BottomGuaranteed = True
286 bottomIsGuaranteed other            = False
287
288 ppStrictnessInfo NoStrictnessInfo = empty
289 ppStrictnessInfo BottomGuaranteed = ptext SLIT("_bot_")
290
291 ppStrictnessInfo (StrictnessInfo wrapper_args wrkr_maybe)
292   = hsep [ptext SLIT("_S_"), text (showList wrapper_args "")]
293 \end{code}
294
295
296 \begin{code}
297 workerExists :: StrictnessInfo -> Bool
298 workerExists (StrictnessInfo _ worker_exists) = worker_exists
299 workerExists other                            = False
300 \end{code}
301
302
303 %************************************************************************
304 %*                                                                      *
305 \subsection[demand-IdInfo]{Demand info about an @Id@}
306 %*                                                                      *
307 %************************************************************************
308
309 Whether a value is certain to be demanded or not.  (This is the
310 information that is computed by the ``front-end'' of the strictness
311 analyser.)
312
313 This information is only used within a module, it is not exported
314 (obviously).
315
316 \begin{code}
317 data DemandInfo
318   = UnknownDemand
319   | DemandedAsPer Demand
320 \end{code}
321
322 \begin{code}
323 noDemandInfo = UnknownDemand
324
325 mkDemandInfo :: Demand -> DemandInfo
326 mkDemandInfo demand = DemandedAsPer demand
327
328 willBeDemanded :: DemandInfo -> Bool
329 willBeDemanded (DemandedAsPer demand) = isStrict demand
330 willBeDemanded _                      = False
331
332 ppDemandInfo UnknownDemand            = text "{-# L #-}"
333 ppDemandInfo (DemandedAsPer info) = hsep [text "{-#", text (showList [info] ""), text "#-}"]
334 \end{code}
335
336
337 %************************************************************************
338 %*                                                                      *
339 \subsection[update-IdInfo]{Update-analysis info about an @Id@}
340 %*                                                                      *
341 %************************************************************************
342
343 \begin{code}
344 data UpdateInfo
345   = NoUpdateInfo
346   | SomeUpdateInfo UpdateSpec
347   deriving (Eq, Ord)
348       -- we need Eq/Ord to cross-chk update infos in interfaces
349
350 -- the form in which we pass update-analysis info between modules:
351 type UpdateSpec = [Int]
352 \end{code}
353
354 \begin{code}
355 mkUpdateInfo = SomeUpdateInfo
356
357 updateInfoMaybe NoUpdateInfo        = Nothing
358 updateInfoMaybe (SomeUpdateInfo []) = Nothing
359 updateInfoMaybe (SomeUpdateInfo  u) = Just u
360 \end{code}
361
362 Text instance so that the update annotations can be read in.
363
364 \begin{code}
365 ppUpdateInfo NoUpdateInfo              = empty
366 ppUpdateInfo (SomeUpdateInfo [])   = empty
367 ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("_U_ ")) (hcat (map int spec))
368 \end{code}
369
370 %************************************************************************
371 %*                                                                      *
372 \subsection[argUsage-IdInfo]{Argument Usage info about an @Id@}
373 %*                                                                      *
374 %************************************************************************
375
376 \begin{code}
377 data ArgUsageInfo
378   = NoArgUsageInfo
379   | SomeArgUsageInfo ArgUsageType
380
381 data ArgUsage = ArgUsage Int    -- number of arguments (is linear!)
382               | UnknownArgUsage
383
384 type ArgUsageType  = [ArgUsage]         -- c_1 -> ... -> BLOB
385 \end{code}
386
387 \begin{code}
388 mkArgUsageInfo [] = NoArgUsageInfo
389 mkArgUsageInfo au = SomeArgUsageInfo au
390
391 getArgUsage :: ArgUsageInfo -> ArgUsageType
392 getArgUsage NoArgUsageInfo        = []
393 getArgUsage (SomeArgUsageInfo u)  = u
394 \end{code}
395
396 \begin{code}
397 {- UNUSED:
398 ppArgUsageInfo NoArgUsageInfo     = empty
399 ppArgUsageInfo (SomeArgUsageInfo aut) = (<>) (ptext SLIT("_L_ ")) (ppArgUsageType aut)
400 -}
401
402 ppArgUsage (ArgUsage n)      = int n
403 ppArgUsage (UnknownArgUsage) = char '-'
404
405 ppArgUsageType aut = hcat
406         [ char '"' ,
407           hcat (punctuate comma (map ppArgUsage aut)),
408           char '"' ]
409 \end{code}
410
411
412 %************************************************************************
413 %*                                                                      *
414 \subsection[FBType-IdInfo]{Type of an expression through Foldr/build's eyes}
415 %*                                                                      *
416 %************************************************************************
417
418 \begin{code}
419 data FBTypeInfo
420   = NoFBTypeInfo
421   | SomeFBTypeInfo FBType
422
423 data FBType = FBType [FBConsum] FBProd deriving (Eq)
424
425 data FBConsum = FBGoodConsum | FBBadConsum deriving(Eq)
426 data FBProd = FBGoodProd | FBBadProd deriving(Eq)
427 \end{code}
428
429 \begin{code}
430 mkFBTypeInfo = SomeFBTypeInfo
431
432 getFBType :: FBTypeInfo -> Maybe FBType
433 getFBType NoFBTypeInfo        = Nothing
434 getFBType (SomeFBTypeInfo u)  = Just u
435 \end{code}
436
437 \begin{code}
438 ppFBTypeInfo NoFBTypeInfo = empty
439 ppFBTypeInfo (SomeFBTypeInfo (FBType cons prod))
440       = (<>) (ptext SLIT("_F_ ")) (ppFBType cons prod)
441
442 ppFBType cons prod = hcat
443         ([ char '"' ] ++ map ppCons cons ++ [ char '-', ppProd prod, char '"' ])
444   where
445         ppCons FBGoodConsum = char 'G'
446         ppCons FBBadConsum  = char 'B'
447         ppProd FBGoodProd   = char 'G'
448         ppProd FBBadProd    = char 'B'
449 \end{code}