[project @ 2000-11-24 17:02:01 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, mkTemplateLocalsNum, 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, isDeadBinder,
26         externallyVisibleId,
27         isIP,
28         isSpecPragmaId, isRecordSelector,
29         isPrimOpId, isPrimOpId_maybe, isDictFunId,
30         isDataConId, isDataConId_maybe, 
31         isDataConWrapId, isDataConWrapId_maybe,
32         isBottomingId,
33         isExportedId, isLocalId, 
34         hasNoBinding,
35
36         -- Inline pragma stuff
37         idInlinePragma, setInlinePragma, modifyInlinePragma, 
38
39
40         -- One shot lambda stuff
41         isOneShotLambda, setOneShotLambda, clearOneShotLambda,
42
43         -- IdInfo stuff
44         setIdUnfolding,
45         setIdArityInfo,
46         setIdDemandInfo,
47         setIdStrictness,
48         setIdTyGenInfo,
49         setIdWorkerInfo,
50         setIdSpecialisation,
51         setIdCafInfo,
52         setIdCprInfo,
53         setIdOccInfo,
54
55         idArity, idArityInfo, 
56         idFlavour,
57         idDemandInfo,
58         idStrictness,
59         idTyGenInfo,
60         idWorkerInfo,
61         idUnfolding,
62         idSpecialisation,
63         idCafInfo,
64         idCprInfo,
65         idLBVarInfo,
66         idOccInfo,
67
68     ) where
69
70 #include "HsVersions.h"
71
72
73 import CoreSyn          ( Unfolding, CoreRules )
74 import BasicTypes       ( Arity )
75 import Var              ( Id, DictId,
76                           isId, mkIdVar,
77                           idName, idType, idUnique, idInfo,
78                           setIdName, setVarType, setIdUnique, 
79                           setIdInfo, lazySetIdInfo, modifyIdInfo, 
80                           maybeModifyIdInfo,
81                           externallyVisibleId
82                         )
83 import Type             ( Type, typePrimRep, addFreeTyVars, 
84                           usOnce, seqType, splitTyConApp_maybe )
85
86 import IdInfo 
87
88 import Demand           ( Demand )
89 import Name             ( Name, OccName,
90                           mkSysLocalName, mkLocalName,
91                           nameIsLocallyDefined,
92                           getOccName, isIPOcc
93                         ) 
94 import OccName          ( UserFS )
95 import PrimRep          ( PrimRep )
96 import TysPrim          ( statePrimTyCon )
97 import FieldLabel       ( FieldLabel )
98 import SrcLoc           ( SrcLoc )
99 import Unique           ( Unique, mkBuiltinUnique, getBuiltinUniques, 
100                           getNumBuiltinUniques )
101 import Outputable
102
103 infixl  1 `setIdUnfolding`,
104           `setIdArityInfo`,
105           `setIdDemandInfo`,
106           `setIdStrictness`,
107           `setIdTyGenInfo`,
108           `setIdWorkerInfo`,
109           `setIdSpecialisation`,
110           `setInlinePragma`,
111           `idCafInfo`,
112           `idCprInfo`
113
114         -- infixl so you can say (id `set` a `set` b)
115 \end{code}
116
117
118
119 %************************************************************************
120 %*                                                                      *
121 \subsection{Simple Id construction}
122 %*                                                                      *
123 %************************************************************************
124
125 Absolutely all Ids are made by mkId.  It 
126         a) Pins free-tyvar-info onto the Id's type, 
127            where it can easily be found.
128         b) Ensures that exported Ids are 
129
130 \begin{code}
131 mkId :: Name -> Type -> IdInfo -> Id
132 mkId name ty info = mkIdVar name (addFreeTyVars ty) info
133 \end{code}
134
135 \begin{code}
136 mkVanillaId :: Name -> Type -> Id
137 mkVanillaId name ty = mkId name ty vanillaIdInfo
138
139 -- SysLocal: for an Id being created by the compiler out of thin air...
140 -- UserLocal: an Id with a name the user might recognize...
141 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
142 mkSysLocal  :: UserFS  -> Unique -> Type -> Id
143
144 mkSysLocal  fs uniq ty      = mkVanillaId (mkSysLocalName uniq fs)      ty
145 mkUserLocal occ uniq ty loc = mkVanillaId (mkLocalName    uniq occ loc) ty
146 \end{code}
147
148 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
149 @Uniques@, but that's OK because the templates are supposed to be
150 instantiated before use.
151
152 \begin{code}
153 -- "Wild Id" typically used when you need a binder that you don't expect to use
154 mkWildId :: Type -> Id
155 mkWildId ty = mkSysLocal SLIT("wild") (mkBuiltinUnique 1) ty
156
157 -- "Template locals" typically used in unfoldings
158 mkTemplateLocals :: [Type] -> [Id]
159 mkTemplateLocals tys = zipWith (mkSysLocal SLIT("tpl"))
160                                (getBuiltinUniques (length tys))
161                                tys
162
163 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
164 mkTemplateLocalsNum n tys = zipWith (mkSysLocal SLIT("tpl"))
165                                (getNumBuiltinUniques n (length tys))
166                                tys
167
168 mkTemplateLocal :: Int -> Type -> Id
169 mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
170 \end{code}
171
172
173 %************************************************************************
174 %*                                                                      *
175 \subsection[Id-general-funs]{General @Id@-related functions}
176 %*                                                                      *
177 %************************************************************************
178
179 \begin{code}
180 setIdType :: Id -> Type -> Id
181         -- Add free tyvar info to the type
182 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
183
184 idPrimRep :: Id -> PrimRep
185 idPrimRep id = typePrimRep (idType id)
186 \end{code}
187
188
189 %************************************************************************
190 %*                                                                      *
191 \subsection{Special Ids}
192 %*                                                                      *
193 %************************************************************************
194
195 \begin{code}
196 idFlavour :: Id -> IdFlavour
197 idFlavour id = flavourInfo (idInfo id)
198
199 setIdNoDiscard :: Id -> Id
200 setIdNoDiscard id       -- Make an Id into a NoDiscardId, unless it is already
201   = modifyIdInfo setNoDiscardInfo id
202
203 recordSelectorFieldLabel :: Id -> FieldLabel
204 recordSelectorFieldLabel id = case idFlavour id of
205                                 RecordSelId lbl -> lbl
206
207 isRecordSelector id = case idFlavour id of
208                         RecordSelId lbl -> True
209                         other           -> False
210
211 isPrimOpId id = case idFlavour id of
212                     PrimOpId op -> True
213                     other       -> False
214
215 isPrimOpId_maybe id = case idFlavour id of
216                             PrimOpId op -> Just op
217                             other       -> Nothing
218
219 isDataConId id = case idFlavour id of
220                         DataConId _ -> True
221                         other       -> False
222
223 isDataConId_maybe id = case idFlavour id of
224                           DataConId con -> Just con
225                           other         -> Nothing
226
227 isDataConWrapId_maybe id = case idFlavour id of
228                                   DataConWrapId con -> Just con
229                                   other             -> Nothing
230
231 isDataConWrapId id = case idFlavour id of
232                         DataConWrapId con -> True
233                         other             -> False
234
235 isSpecPragmaId id = case idFlavour id of
236                         SpecPragmaId -> True
237                         other        -> False
238
239 hasNoBinding id = case idFlavour id of
240                         DataConId _ -> True
241                         PrimOpId _  -> True
242                         other       -> False
243         -- hasNoBinding returns True of an Id which may not have a
244         -- binding, even though it is defined in this module.  Notably,
245         -- the constructors of a dictionary are in this situation.
246
247 isDictFunId id = case idFlavour id of
248                    DictFunId -> True
249                    other     -> False
250
251 -- Don't drop a binding for an exported Id,
252 -- if it otherwise looks dead.  
253 -- Perhaps a better name would be isDiscardableId
254 isExportedId :: Id -> Bool
255 isExportedId id = case idFlavour id of
256                         VanillaId  -> False
257                         other      -> True
258
259 isLocalId :: Id -> Bool
260 -- True of Ids that are locally defined, but are not constants
261 -- like data constructors, record selectors, and the like. 
262 -- See comments with CoreFVs.isLocalVar
263 isLocalId id 
264 #ifdef DEBUG
265   | not (isId id) = pprTrace "isLocalid" (ppr id) False
266   | otherwise
267 #endif
268   = case idFlavour id of
269          VanillaId    -> True
270          ExportedId   -> True
271          SpecPragmaId -> True
272          other        -> False
273 \end{code}
274
275
276 omitIfaceSigForId tells whether an Id's info is implied by other declarations,
277 so we don't need to put its signature in an interface file, even if it's mentioned
278 in some other interface unfolding.
279
280 \begin{code}
281 omitIfaceSigForId :: Id -> Bool
282 omitIfaceSigForId id
283   = ASSERT2( not (omit && nameIsLocallyDefined (idName id)
284                        && idTyGenInfo id /= TyGenNever),
285              ppr id )
286     -- mustn't omit type signature for a name whose type might change!
287     omit
288   where
289     omit = omitIfaceSigForId' id
290
291 omitIfaceSigForId' id
292   = case idFlavour id of
293         RecordSelId _   -> True -- Includes dictionary selectors
294         PrimOpId _      -> True
295         DataConId _     -> True
296         DataConWrapId _ -> True
297                 -- These are are implied by their type or class decl;
298                 -- remember that all type and class decls appear in the interface file.
299                 -- The dfun id must *not* be omitted, because it carries version info for
300                 -- the instance decl
301
302         ConstantId -> False     -- Ordinary Ids
303         DictFunId  -> False
304         
305         ExportedId   -> False   -- I don't think these happen
306         VanillaId    -> False   -- ditto
307         SpecPragmaId -> False   -- ditto
308 \end{code}
309
310 \begin{code}
311 isDeadBinder :: Id -> Bool
312 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
313                   | otherwise = False   -- TyVars count as not dead
314
315 isIP id = isIPOcc (getOccName id)
316 \end{code}
317
318
319 %************************************************************************
320 %*                                                                      *
321 \subsection{IdInfo stuff}
322 %*                                                                      *
323 %************************************************************************
324
325 \begin{code}
326         ---------------------------------
327         -- ARITY
328 idArityInfo :: Id -> ArityInfo
329 idArityInfo id = arityInfo (idInfo id)
330
331 idArity :: Id -> Arity
332 idArity id = arityLowerBound (idArityInfo id)
333
334 setIdArityInfo :: Id -> ArityInfo -> Id
335 setIdArityInfo id arity = modifyIdInfo (`setArityInfo` arity) id
336
337         ---------------------------------
338         -- STRICTNESS
339 idStrictness :: Id -> StrictnessInfo
340 idStrictness id = strictnessInfo (idInfo id)
341
342 setIdStrictness :: Id -> StrictnessInfo -> Id
343 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
344
345 -- isBottomingId returns true if an application to n args would diverge
346 isBottomingId :: Id -> Bool
347 isBottomingId id = isBottomingStrictness (idStrictness id)
348
349         ---------------------------------
350         -- TYPE GENERALISATION
351 idTyGenInfo :: Id -> TyGenInfo
352 idTyGenInfo id = tyGenInfo (idInfo id)
353
354 setIdTyGenInfo :: Id -> TyGenInfo -> Id
355 setIdTyGenInfo id tygen_info = modifyIdInfo (`setTyGenInfo` tygen_info) id
356
357         ---------------------------------
358         -- WORKER ID
359 idWorkerInfo :: Id -> WorkerInfo
360 idWorkerInfo id = workerInfo (idInfo id)
361
362 setIdWorkerInfo :: Id -> WorkerInfo -> Id
363 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
364
365         ---------------------------------
366         -- UNFOLDING
367 idUnfolding :: Id -> Unfolding
368 idUnfolding id = unfoldingInfo (idInfo id)
369
370 setIdUnfolding :: Id -> Unfolding -> Id
371 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
372
373         ---------------------------------
374         -- DEMAND
375 idDemandInfo :: Id -> Demand
376 idDemandInfo id = demandInfo (idInfo id)
377
378 setIdDemandInfo :: Id -> Demand -> Id
379 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
380
381         ---------------------------------
382         -- SPECIALISATION
383 idSpecialisation :: Id -> CoreRules
384 idSpecialisation id = specInfo (idInfo id)
385
386 setIdSpecialisation :: Id -> CoreRules -> Id
387 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
388
389         ---------------------------------
390         -- CAF INFO
391 idCafInfo :: Id -> CafInfo
392 idCafInfo id = cafInfo (idInfo id)
393
394 setIdCafInfo :: Id -> CafInfo -> Id
395 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
396
397         ---------------------------------
398         -- CPR INFO
399 idCprInfo :: Id -> CprInfo
400 idCprInfo id = cprInfo (idInfo id)
401
402 setIdCprInfo :: Id -> CprInfo -> Id
403 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
404
405         ---------------------------------
406         -- Occcurrence INFO
407 idOccInfo :: Id -> OccInfo
408 idOccInfo id = occInfo (idInfo id)
409
410 setIdOccInfo :: Id -> OccInfo -> Id
411 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
412 \end{code}
413
414
415         ---------------------------------
416         -- INLINING
417 The inline pragma tells us to be very keen to inline this Id, but it's still
418 OK not to if optimisation is switched off.
419
420 \begin{code}
421 idInlinePragma :: Id -> InlinePragInfo
422 idInlinePragma id = inlinePragInfo (idInfo id)
423
424 setInlinePragma :: Id -> InlinePragInfo -> Id
425 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
426
427 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
428 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
429 \end{code}
430
431
432         ---------------------------------
433         -- ONE-SHOT LAMBDAS
434 \begin{code}
435 idLBVarInfo :: Id -> LBVarInfo
436 idLBVarInfo id = lbvarInfo (idInfo id)
437
438 isOneShotLambda :: Id -> Bool
439 isOneShotLambda id = analysis || hack
440   where analysis = case idLBVarInfo id of
441                      LBVarInfo u    | u == usOnce             -> True
442                      other                                    -> False
443         hack     = case splitTyConApp_maybe (idType id) of
444                      Just (tycon,_) | tycon == statePrimTyCon -> True
445                      other                                    -> False
446
447         -- The last clause is a gross hack.  It claims that 
448         -- every function over realWorldStatePrimTy is a one-shot
449         -- function.  This is pretty true in practice, and makes a big
450         -- difference.  For example, consider
451         --      a `thenST` \ r -> ...E...
452         -- The early full laziness pass, if it doesn't know that r is one-shot
453         -- will pull out E (let's say it doesn't mention r) to give
454         --      let lvl = E in a `thenST` \ r -> ...lvl...
455         -- When `thenST` gets inlined, we end up with
456         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
457         -- and we don't re-inline E.
458         --
459         -- It would be better to spot that r was one-shot to start with, but
460         -- I don't want to rely on that.
461         --
462         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
463         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
464
465 setOneShotLambda :: Id -> Id
466 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` LBVarInfo usOnce) id
467
468 clearOneShotLambda :: Id -> Id
469 clearOneShotLambda id 
470   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
471   | otherwise          = id                     
472
473 -- But watch out: this may change the type of something else
474 --      f = \x -> e
475 -- If we change the one-shot-ness of x, f's type changes
476 \end{code}
477
478 \begin{code}
479 zapFragileIdInfo :: Id -> Id
480 zapFragileIdInfo id = maybeModifyIdInfo zapFragileInfo id
481
482 zapLamIdInfo :: Id -> Id
483 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
484 \end{code}
485