7e1c8d56beda3283fc78ec765907099ab1f8ed7d
[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      -- user requests that we inline this
184
185   | IDontWantToBeINLINEd  -- user requests that we don't inline this
186
187   | IMustNotBeINLINEd   -- Used by the simplifier to prevent looping
188                         -- on recursive definitions
189
190   | IMustBeINLINEd      -- Absolutely must inline; used for PrimOps only
191 \end{code}
192
193
194 %************************************************************************
195 %*                                                                      *
196 \subsection[specialisation-IdInfo]{Specialisation info about an @Id@}
197 %*                                                                      *
198 %************************************************************************
199
200 A @IdSpecEnv@ holds details of an @Id@'s specialisations. 
201
202 \begin{code}
203 type IdSpecEnv = SpecEnv CoreExpr
204 \end{code}
205
206 For example, if \tr{f}'s @SpecEnv@ contains the mapping:
207 \begin{verbatim}
208         [List a, b]  ===>  (\d -> f' a b)
209 \end{verbatim}
210 then when we find an application of f to matching types, we simply replace
211 it by the matching RHS:
212 \begin{verbatim}
213         f (List Int) Bool ===>  (\d -> f' Int Bool)
214 \end{verbatim}
215 All the stuff about how many dictionaries to discard, and what types
216 to apply the specialised function to, are handled by the fact that the
217 SpecEnv contains a template for the result of the specialisation.
218
219 There is one more exciting case, which is dealt with in exactly the same
220 way.  If the specialised value is unboxed then it is lifted at its
221 definition site and unlifted at its uses.  For example:
222
223         pi :: forall a. Num a => a
224
225 might have a specialisation
226
227         [Int#] ===>  (case pi' of Lift pi# -> pi#)
228
229 where pi' :: Lift Int# is the specialised version of pi.
230
231
232
233 %************************************************************************
234 %*                                                                      *
235 \subsection[strictness-IdInfo]{Strictness info about an @Id@}
236 %*                                                                      *
237 %************************************************************************
238
239 We specify the strictness of a function by giving information about
240 each of the ``wrapper's'' arguments (see the description about
241 worker/wrapper-style transformations in the PJ/Launchbury paper on
242 unboxed types).
243
244 The list of @Demands@ specifies: (a)~the strictness properties
245 of a function's arguments; (b)~the {\em existence} of a ``worker''
246 version of the function; and (c)~the type signature of that worker (if
247 it exists); i.e. its calling convention.
248
249 \begin{code}
250 data StrictnessInfo
251   = NoStrictnessInfo
252
253   | BottomGuaranteed    -- This Id guarantees never to return;
254                         -- it is bottom regardless of its arguments.
255                         -- Useful for "error" and other disguised
256                         -- variants thereof.
257
258   | StrictnessInfo [Demand] 
259                    Bool         -- True <=> there is a worker. There might not be, even for a
260                                 -- strict function, because:
261                                 --      (a) the function might be small enough to inline, 
262                                 --          so no need for w/w split
263                                 --      (b) the strictness info might be "SSS" or something, so no w/w split.
264
265                                 -- Worker's Id, if applicable, and a list of the constructors
266                                 -- mentioned by the wrapper.  This is necessary so that the
267                                 -- renamer can slurp them in.  Without this info, the renamer doesn't
268                                 -- know which data types to slurp in concretely.  Remember, for
269                                 -- strict things we don't put the unfolding in the interface file, to save space.
270                                 -- This constructor list allows the renamer to behave much as if the
271                                 -- unfolding *was* in the interface file.
272 \end{code}
273
274 \begin{code}
275 mkStrictnessInfo :: [Demand] -> Bool -> StrictnessInfo
276
277 mkStrictnessInfo xs has_wrkr
278   | all is_lazy xs       = NoStrictnessInfo             -- Uninteresting
279   | otherwise            = StrictnessInfo xs has_wrkr
280   where
281     is_lazy (WwLazy False) = True       -- NB "Absent" args do *not* count!
282     is_lazy _              = False      -- (as they imply a worker)
283
284 noStrictnessInfo       = NoStrictnessInfo
285 mkBottomStrictnessInfo = BottomGuaranteed
286
287 bottomIsGuaranteed BottomGuaranteed = True
288 bottomIsGuaranteed other            = False
289
290 ppStrictnessInfo NoStrictnessInfo = empty
291 ppStrictnessInfo BottomGuaranteed = ptext SLIT("_bot_")
292
293 ppStrictnessInfo (StrictnessInfo wrapper_args wrkr_maybe)
294   = hsep [ptext SLIT("_S_"), text (showList wrapper_args "")]
295 \end{code}
296
297
298 \begin{code}
299 workerExists :: StrictnessInfo -> Bool
300 workerExists (StrictnessInfo _ worker_exists) = worker_exists
301 workerExists other                            = False
302 \end{code}
303
304
305 %************************************************************************
306 %*                                                                      *
307 \subsection[demand-IdInfo]{Demand info about an @Id@}
308 %*                                                                      *
309 %************************************************************************
310
311 Whether a value is certain to be demanded or not.  (This is the
312 information that is computed by the ``front-end'' of the strictness
313 analyser.)
314
315 This information is only used within a module, it is not exported
316 (obviously).
317
318 \begin{code}
319 data DemandInfo
320   = UnknownDemand
321   | DemandedAsPer Demand
322 \end{code}
323
324 \begin{code}
325 noDemandInfo = UnknownDemand
326
327 mkDemandInfo :: Demand -> DemandInfo
328 mkDemandInfo demand = DemandedAsPer demand
329
330 willBeDemanded :: DemandInfo -> Bool
331 willBeDemanded (DemandedAsPer demand) = isStrict demand
332 willBeDemanded _                      = False
333
334 ppDemandInfo UnknownDemand            = text "{-# L #-}"
335 ppDemandInfo (DemandedAsPer info) = hsep [text "{-#", text (showList [info] ""), text "#-}"]
336 \end{code}
337
338
339 %************************************************************************
340 %*                                                                      *
341 \subsection[update-IdInfo]{Update-analysis info about an @Id@}
342 %*                                                                      *
343 %************************************************************************
344
345 \begin{code}
346 data UpdateInfo
347   = NoUpdateInfo
348   | SomeUpdateInfo UpdateSpec
349   deriving (Eq, Ord)
350       -- we need Eq/Ord to cross-chk update infos in interfaces
351
352 -- the form in which we pass update-analysis info between modules:
353 type UpdateSpec = [Int]
354 \end{code}
355
356 \begin{code}
357 mkUpdateInfo = SomeUpdateInfo
358
359 updateInfoMaybe NoUpdateInfo        = Nothing
360 updateInfoMaybe (SomeUpdateInfo []) = Nothing
361 updateInfoMaybe (SomeUpdateInfo  u) = Just u
362 \end{code}
363
364 Text instance so that the update annotations can be read in.
365
366 \begin{code}
367 ppUpdateInfo NoUpdateInfo              = empty
368 ppUpdateInfo (SomeUpdateInfo [])   = empty
369 ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("_U_ ")) (hcat (map int spec))
370 \end{code}
371
372 %************************************************************************
373 %*                                                                      *
374 \subsection[argUsage-IdInfo]{Argument Usage info about an @Id@}
375 %*                                                                      *
376 %************************************************************************
377
378 \begin{code}
379 data ArgUsageInfo
380   = NoArgUsageInfo
381   | SomeArgUsageInfo ArgUsageType
382
383 data ArgUsage = ArgUsage Int    -- number of arguments (is linear!)
384               | UnknownArgUsage
385
386 type ArgUsageType  = [ArgUsage]         -- c_1 -> ... -> BLOB
387 \end{code}
388
389 \begin{code}
390 mkArgUsageInfo [] = NoArgUsageInfo
391 mkArgUsageInfo au = SomeArgUsageInfo au
392
393 getArgUsage :: ArgUsageInfo -> ArgUsageType
394 getArgUsage NoArgUsageInfo        = []
395 getArgUsage (SomeArgUsageInfo u)  = u
396 \end{code}
397
398 \begin{code}
399 {- UNUSED:
400 ppArgUsageInfo NoArgUsageInfo     = empty
401 ppArgUsageInfo (SomeArgUsageInfo aut) = (<>) (ptext SLIT("_L_ ")) (ppArgUsageType aut)
402 -}
403
404 ppArgUsage (ArgUsage n)      = int n
405 ppArgUsage (UnknownArgUsage) = char '-'
406
407 ppArgUsageType aut = hcat
408         [ char '"' ,
409           hcat (punctuate comma (map ppArgUsage aut)),
410           char '"' ]
411 \end{code}
412
413
414 %************************************************************************
415 %*                                                                      *
416 \subsection[FBType-IdInfo]{Type of an expression through Foldr/build's eyes}
417 %*                                                                      *
418 %************************************************************************
419
420 \begin{code}
421 data FBTypeInfo
422   = NoFBTypeInfo
423   | SomeFBTypeInfo FBType
424
425 data FBType = FBType [FBConsum] FBProd deriving (Eq)
426
427 data FBConsum = FBGoodConsum | FBBadConsum deriving(Eq)
428 data FBProd = FBGoodProd | FBBadProd deriving(Eq)
429 \end{code}
430
431 \begin{code}
432 mkFBTypeInfo = SomeFBTypeInfo
433
434 getFBType :: FBTypeInfo -> Maybe FBType
435 getFBType NoFBTypeInfo        = Nothing
436 getFBType (SomeFBTypeInfo u)  = Just u
437 \end{code}
438
439 \begin{code}
440 ppFBTypeInfo NoFBTypeInfo = empty
441 ppFBTypeInfo (SomeFBTypeInfo (FBType cons prod))
442       = (<>) (ptext SLIT("_F_ ")) (ppFBType cons prod)
443
444 ppFBType cons prod = hcat
445         ([ char '"' ] ++ map ppCons cons ++ [ char '-', ppProd prod, char '"' ])
446   where
447         ppCons FBGoodConsum = char 'G'
448         ppCons FBBadConsum  = char 'B'
449         ppProd FBGoodProd   = char 'G'
450         ppProd FBBadProd    = char 'B'
451 \end{code}