[project @ 2000-01-04 17:40:46 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Id.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[Id]{@Ids@: Value and constructor identifiers}
5
6 \begin{code}
7 module Id (
8         Id, DictId,
9
10         -- Simple construction
11         mkId, mkVanillaId, mkSysLocal, mkUserLocal,
12         mkTemplateLocals, mkWildId, mkTemplateLocal,
13
14         -- Taking an Id apart
15         idName, idType, idUnique, idInfo,
16         idPrimRep, isId,
17         recordSelectorFieldLabel,
18
19         -- Modifying an Id
20         setIdName, setIdUnique, setIdType, setIdNoDiscard, 
21         setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo,
22         zapFragileIdInfo, zapLamIdInfo,
23
24         -- Predicates
25         omitIfaceSigForId,
26         exportWithOrigOccName,
27         externallyVisibleId,
28         idFreeTyVars, 
29
30         -- Inline pragma stuff
31         getInlinePragma, setInlinePragma, modifyInlinePragma, 
32
33         isSpecPragmaId, isRecordSelector,
34         isPrimitiveId_maybe, isDataConId_maybe,
35         isConstantId, isConstantId_maybe, isBottomingId, idAppIsBottom,
36         isExportedId, isUserExportedId,
37         mayHaveNoBinding,
38
39         -- One shot lambda stuff
40         isOneShotLambda, setOneShotLambda, clearOneShotLambda,
41
42         -- IdInfo stuff
43         setIdUnfolding,
44         setIdArity,
45         setIdDemandInfo,
46         setIdStrictness,
47         setIdWorkerInfo,
48         setIdSpecialisation,
49         setIdUpdateInfo,
50         setIdCafInfo,
51         setIdCprInfo,
52         setIdOccInfo,
53
54         getIdArity,
55         getIdDemandInfo,
56         getIdStrictness,
57         getIdWorkerInfo,
58         getIdUnfolding,
59         getIdSpecialisation,
60         getIdUpdateInfo,
61         getIdCafInfo,
62         getIdCprInfo,
63         getIdOccInfo
64
65     ) where
66
67 #include "HsVersions.h"
68
69 import {-# SOURCE #-} CoreUnfold ( Unfolding )
70 import {-# SOURCE #-} CoreSyn    ( CoreRules )
71
72 import Var              ( Id, DictId,
73                           isId, mkIdVar,
74                           idName, idType, idUnique, idInfo,
75                           setIdName, setVarType, setIdUnique, 
76                           setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo,
77                           externallyVisibleId
78                         )
79 import VarSet
80 import Type             ( Type, tyVarsOfType, typePrimRep, addFreeTyVars, seqType, splitTyConApp_maybe )
81
82 import IdInfo 
83
84 import Demand           ( Demand, isStrict, wwLazy )
85 import Name             ( Name, OccName,
86                           mkSysLocalName, mkLocalName,
87                           isWiredInName, isUserExportedName
88                         ) 
89 import OccName          ( UserFS )
90 import Const            ( Con(..) )
91 import PrimRep          ( PrimRep )
92 import PrimOp           ( PrimOp )
93 import TysPrim          ( statePrimTyCon )
94 import FieldLabel       ( FieldLabel(..) )
95 import SrcLoc           ( SrcLoc )
96 import Unique           ( Unique, mkBuiltinUnique, getBuiltinUniques )
97 import Outputable
98
99 infixl  1 `setIdUnfolding`,
100           `setIdArity`,
101           `setIdDemandInfo`,
102           `setIdStrictness`,
103           `setIdWorkerInfo`,
104           `setIdSpecialisation`,
105           `setIdUpdateInfo`,
106           `setInlinePragma`,
107           `getIdCafInfo`,
108           `getIdCprInfo`
109
110         -- infixl so you can say (id `set` a `set` b)
111 \end{code}
112
113
114
115 %************************************************************************
116 %*                                                                      *
117 \subsection{Simple Id construction}
118 %*                                                                      *
119 %************************************************************************
120
121 Absolutely all Ids are made by mkId.  It 
122         a) Pins free-tyvar-info onto the Id's type, 
123            where it can easily be found.
124         b) Ensures that exported Ids are 
125
126 \begin{code}
127 mkId :: Name -> Type -> IdInfo -> Id
128 mkId name ty info = mkIdVar name (addFreeTyVars ty) info'
129                   where
130                     info' | isUserExportedName name = setNoDiscardInfo info
131                           | otherwise               = info
132 \end{code}
133
134 \begin{code}
135 mkVanillaId :: Name -> Type -> Id
136 mkVanillaId name ty = mkId name ty vanillaIdInfo
137
138 -- SysLocal: for an Id being created by the compiler out of thin air...
139 -- UserLocal: an Id with a name the user might recognize...
140 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
141 mkSysLocal  :: UserFS  -> Unique -> Type -> Id
142
143 mkSysLocal  fs uniq ty      = mkVanillaId (mkSysLocalName uniq fs)      ty
144 mkUserLocal occ uniq ty loc = mkVanillaId (mkLocalName    uniq occ loc) ty
145 \end{code}
146
147 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
148 @Uniques@, but that's OK because the templates are supposed to be
149 instantiated before use.
150
151 \begin{code}
152 -- "Wild Id" typically used when you need a binder that you don't expect to use
153 mkWildId :: Type -> Id
154 mkWildId ty = mkSysLocal SLIT("wild") (mkBuiltinUnique 1) ty
155
156 -- "Template locals" typically used in unfoldings
157 mkTemplateLocals :: [Type] -> [Id]
158 mkTemplateLocals tys = zipWith (mkSysLocal SLIT("tpl"))
159                                (getBuiltinUniques (length tys))
160                                tys
161
162 mkTemplateLocal :: Int -> Type -> Id
163 mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
164 \end{code}
165
166
167 %************************************************************************
168 %*                                                                      *
169 \subsection[Id-general-funs]{General @Id@-related functions}
170 %*                                                                      *
171 %************************************************************************
172
173 \begin{code}
174 idFreeTyVars :: Id -> TyVarSet
175 idFreeTyVars id = tyVarsOfType (idType id)
176
177 setIdType :: Id -> Type -> Id
178         -- Add free tyvar info to the type
179 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
180
181 idPrimRep :: Id -> PrimRep
182 idPrimRep id = typePrimRep (idType id)
183 \end{code}
184
185
186 %************************************************************************
187 %*                                                                      *
188 \subsection{Special Ids}
189 %*                                                                      *
190 %************************************************************************
191
192 \begin{code}
193 idFlavour :: Id -> IdFlavour
194 idFlavour id = flavourInfo (idInfo id)
195
196 setIdNoDiscard :: Id -> Id
197 setIdNoDiscard id       -- Make an Id into a NoDiscardId, unless it is already
198   = modifyIdInfo setNoDiscardInfo id
199
200 recordSelectorFieldLabel :: Id -> FieldLabel
201 recordSelectorFieldLabel id = case idFlavour id of
202                                 RecordSelId lbl -> lbl
203
204 isRecordSelector id = case idFlavour id of
205                         RecordSelId lbl -> True
206                         other           -> False
207
208 isPrimitiveId_maybe id = case idFlavour id of
209                             ConstantId (PrimOp op) -> Just op
210                             other                  -> Nothing
211
212 isDataConId_maybe id = case idFlavour id of
213                           ConstantId (DataCon con) -> Just con
214                           other                    -> Nothing
215
216 isConstantId id = case idFlavour id of
217                     ConstantId _ -> True
218                     other        -> False
219
220 isConstantId_maybe id = case idFlavour id of
221                           ConstantId const -> Just const
222                           other            -> Nothing
223
224 isSpecPragmaId id = case idFlavour id of
225                         SpecPragmaId -> True
226                         other        -> False
227
228 mayHaveNoBinding id = isConstantId id
229         -- mayHaveNoBinding returns True of an Id which may not have a
230         -- binding, even though it is defined in this module.  Notably,
231         -- the constructors of a dictionary are in this situation.
232         --      
233         -- mayHaveNoBinding returns True of some things that *do* have a local binding,
234         -- so it's only an approximation.  That's ok... it's only use for assertions.
235
236 -- Don't drop a binding for an exported Id,
237 -- if it otherwise looks dead.  
238 isExportedId :: Id -> Bool
239 isExportedId id = case idFlavour id of
240                         VanillaId -> False
241                         other     -> True       -- All the others are no-discard
242
243 -- Say if an Id was exported by the user
244 -- Implies isExportedId (see mkId above)
245 isUserExportedId :: Id -> Bool
246 isUserExportedId id = isUserExportedName (idName id)
247 \end{code}
248
249
250 omitIfaceSigForId tells whether an Id's info is implied by other declarations,
251 so we don't need to put its signature in an interface file, even if it's mentioned
252 in some other interface unfolding.
253
254 \begin{code}
255 omitIfaceSigForId :: Id -> Bool
256 omitIfaceSigForId id
257   | isWiredInName (idName id)
258   = True
259
260   | otherwise
261   = case idFlavour id of
262         RecordSelId _  -> True  -- Includes dictionary selectors
263         ConstantId _   -> True
264                 -- ConstantIds are implied by their type or class decl;
265                 -- remember that all type and class decls appear in the interface file.
266                 -- The dfun id must *not* be omitted, because it carries version info for
267                 -- the instance decl
268
269         other          -> False -- Don't omit!
270
271 -- Certain names must be exported with their original occ names, because
272 -- these names are bound by either a class declaration or a data declaration
273 -- or an explicit user export.
274 exportWithOrigOccName :: Id -> Bool
275 exportWithOrigOccName id = omitIfaceSigForId id || isUserExportedId id
276 \end{code}
277
278
279
280 %************************************************************************
281 %*                                                                      *
282 \subsection{IdInfo stuff}
283 %*                                                                      *
284 %************************************************************************
285
286 \begin{code}
287         ---------------------------------
288         -- ARITY
289 getIdArity :: Id -> ArityInfo
290 getIdArity id = arityInfo (idInfo id)
291
292 setIdArity :: Id -> ArityInfo -> Id
293 setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id
294
295         ---------------------------------
296         -- STRICTNESS
297 getIdStrictness :: Id -> StrictnessInfo
298 getIdStrictness id = strictnessInfo (idInfo id)
299
300 setIdStrictness :: Id -> StrictnessInfo -> Id
301 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
302
303 -- isBottomingId returns true if an application to n args would diverge
304 isBottomingId :: Id -> Bool
305 isBottomingId id = isBottomingStrictness (strictnessInfo (idInfo id))
306
307 idAppIsBottom :: Id -> Int -> Bool
308 idAppIsBottom id n = appIsBottom (strictnessInfo (idInfo id)) n
309
310         ---------------------------------
311         -- WORKER ID
312 getIdWorkerInfo :: Id -> WorkerInfo
313 getIdWorkerInfo id = workerInfo (idInfo id)
314
315 setIdWorkerInfo :: Id -> WorkerInfo -> Id
316 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
317
318         ---------------------------------
319         -- UNFOLDING
320 getIdUnfolding :: Id -> Unfolding
321 getIdUnfolding id = unfoldingInfo (idInfo id)
322
323 setIdUnfolding :: Id -> Unfolding -> Id
324 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
325
326         ---------------------------------
327         -- DEMAND
328 getIdDemandInfo :: Id -> Demand
329 getIdDemandInfo id = demandInfo (idInfo id)
330
331 setIdDemandInfo :: Id -> Demand -> Id
332 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
333
334         ---------------------------------
335         -- UPDATE INFO
336 getIdUpdateInfo :: Id -> UpdateInfo
337 getIdUpdateInfo id = updateInfo (idInfo id)
338
339 setIdUpdateInfo :: Id -> UpdateInfo -> Id
340 setIdUpdateInfo id upd_info = modifyIdInfo (`setUpdateInfo` upd_info) id
341
342         ---------------------------------
343         -- SPECIALISATION
344 getIdSpecialisation :: Id -> CoreRules
345 getIdSpecialisation id = specInfo (idInfo id)
346
347 setIdSpecialisation :: Id -> CoreRules -> Id
348 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
349
350         ---------------------------------
351         -- CAF INFO
352 getIdCafInfo :: Id -> CafInfo
353 getIdCafInfo id = cafInfo (idInfo id)
354
355 setIdCafInfo :: Id -> CafInfo -> Id
356 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
357
358         ---------------------------------
359         -- CPR INFO
360 getIdCprInfo :: Id -> CprInfo
361 getIdCprInfo id = cprInfo (idInfo id)
362
363 setIdCprInfo :: Id -> CprInfo -> Id
364 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
365
366         ---------------------------------
367         -- Occcurrence INFO
368 getIdOccInfo :: Id -> OccInfo
369 getIdOccInfo id = occInfo (idInfo id)
370
371 setIdOccInfo :: Id -> OccInfo -> Id
372 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
373 \end{code}
374
375
376         ---------------------------------
377         -- INLINING
378 The inline pragma tells us to be very keen to inline this Id, but it's still
379 OK not to if optimisation is switched off.
380
381 \begin{code}
382 getInlinePragma :: Id -> InlinePragInfo
383 getInlinePragma id = inlinePragInfo (idInfo id)
384
385 setInlinePragma :: Id -> InlinePragInfo -> Id
386 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
387
388 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
389 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
390 \end{code}
391
392
393         ---------------------------------
394         -- ONE-SHOT LAMBDAS
395 \begin{code}
396 isOneShotLambda :: Id -> Bool
397 isOneShotLambda id = case lbvarInfo (idInfo id) of
398                         IsOneShotLambda -> True
399                         NoLBVarInfo     -> case splitTyConApp_maybe (idType id) of
400                                                 Just (tycon,_) -> tycon == statePrimTyCon
401                                                 other          -> False
402         -- The last clause is a gross hack.  It claims that 
403         -- every function over realWorldStatePrimTy is a one-shot
404         -- function.  This is pretty true in practice, and makes a big
405         -- difference.  For example, consider
406         --      a `thenST` \ r -> ...E...
407         -- The early full laziness pass, if it doesn't know that r is one-shot
408         -- will pull out E (let's say it doesn't mention r) to give
409         --      let lvl = E in a `thenST` \ r -> ...lvl...
410         -- When `thenST` gets inlined, we end up with
411         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
412         -- and we don't re-inline E.
413         --
414         -- It would be better to spot that r was one-shot to start with, but
415         -- I don't want to rely on that.
416         --
417         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
418         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
419
420 setOneShotLambda :: Id -> Id
421 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
422
423 clearOneShotLambda :: Id -> Id
424 clearOneShotLambda id 
425   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
426   | otherwise          = id                     
427
428 -- But watch out: this may change the type of something else
429 --      f = \x -> e
430 -- If we change the one-shot-ness of x, f's type changes
431 \end{code}
432
433 \begin{code}
434 zapFragileIdInfo :: Id -> Id
435 zapFragileIdInfo id = maybeModifyIdInfo zapFragileInfo id
436
437 zapLamIdInfo :: Id -> Id
438 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
439 \end{code}
440