[project @ 2003-03-20 12:20:06 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         mkGlobalId, mkLocalId, mkSpecPragmaId, mkLocalIdWithInfo,
12         mkSysLocal, mkSysLocalUnencoded, mkUserLocal, mkVanillaGlobal,
13         mkTemplateLocals, mkTemplateLocalsNum, mkWildId, mkTemplateLocal,
14         mkWorkerId,
15
16         -- Taking an Id apart
17         idName, idType, idUnique, idInfo,
18         idPrimRep, isId, globalIdDetails,
19         recordSelectorFieldLabel,
20
21         -- Modifying an Id
22         setIdName, setIdUnique, setIdType, setIdLocalExported, setGlobalIdDetails,
23         setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo,
24         zapLamIdInfo, zapDemandIdInfo, 
25
26         -- Predicates
27         isImplicitId, isDeadBinder,
28         isSpecPragmaId, isExportedId, isLocalId, isGlobalId,
29         isRecordSelector,
30         isPrimOpId, isPrimOpId_maybe, 
31         isFCallId, isFCallId_maybe,
32         isDataConWorkId, isDataConWorkId_maybe, 
33         isDataConWrapId, isDataConWrapId_maybe,
34         isBottomingId,
35         hasNoBinding,
36
37         -- Inline pragma stuff
38         idInlinePragma, setInlinePragma, modifyInlinePragma, 
39
40
41         -- One shot lambda stuff
42         isOneShotLambda, setOneShotLambda, clearOneShotLambda,
43
44         -- IdInfo stuff
45         setIdUnfolding,
46         setIdArity,
47         setIdNewDemandInfo, 
48         setIdNewStrictness, zapIdNewStrictness,
49         setIdWorkerInfo,
50         setIdSpecialisation,
51         setIdCafInfo,
52         setIdOccInfo,
53
54 #ifdef OLD_STRICTNESS
55         idDemandInfo, 
56         idStrictness, 
57         idCprInfo,
58         setIdStrictness, 
59         setIdDemandInfo, 
60         setIdCprInfo,
61 #endif
62
63         idArity, 
64         idNewDemandInfo, idNewDemandInfo_maybe,
65         idNewStrictness, idNewStrictness_maybe, 
66         idWorkerInfo,
67         idUnfolding,
68         idSpecialisation, idCoreRules,
69         idCafInfo,
70         idLBVarInfo,
71         idOccInfo,
72
73 #ifdef OLD_STRICTNESS
74         newStrictnessFromOld    -- Temporary
75 #endif
76
77     ) where
78
79 #include "HsVersions.h"
80
81
82 import CoreSyn          ( Unfolding, CoreRules, IdCoreRule, rulesRules )
83 import BasicTypes       ( Arity )
84 import Var              ( Id, DictId,
85                           isId, isExportedId, isSpecPragmaId, isLocalId,
86                           idName, idType, idUnique, idInfo, isGlobalId,
87                           setIdName, setVarType, setIdUnique, setIdLocalExported,
88                           setIdInfo, lazySetIdInfo, modifyIdInfo, 
89                           maybeModifyIdInfo,
90                           globalIdDetails, setGlobalIdDetails
91                         )
92 import qualified Var    ( mkLocalId, mkGlobalId, mkSpecPragmaId )
93 import Type             ( Type, typePrimRep, addFreeTyVars, 
94                           seqType, splitTyConApp_maybe )
95
96 import IdInfo 
97
98 import qualified Demand ( Demand )
99 import DataCon          ( isUnboxedTupleCon )
100 import NewDemand        ( Demand, StrictSig, topDmd, topSig, isBottomingSig )
101 import Name             ( Name, OccName,
102                           mkSystemName, mkSystemNameEncoded, mkInternalName,
103                           getOccName, getSrcLoc
104                         ) 
105 import OccName          ( EncodedFS, mkWorkerOcc )
106 import PrimRep          ( PrimRep )
107 import FieldLabel       ( FieldLabel )
108 import Maybes           ( orElse )
109 import SrcLoc           ( SrcLoc )
110 import Outputable
111 import Unique           ( Unique, mkBuiltinUnique )
112
113 -- infixl so you can say (id `set` a `set` b)
114 infixl  1 `setIdUnfolding`,
115           `setIdArity`,
116           `setIdNewDemandInfo`,
117           `setIdNewStrictness`,
118           `setIdWorkerInfo`,
119           `setIdSpecialisation`,
120           `setInlinePragma`,
121           `idCafInfo`
122 #ifdef OLD_STRICTNESS
123           ,`idCprInfo`
124           ,`setIdStrictness`
125           ,`setIdDemandInfo`
126 #endif
127 \end{code}
128
129
130
131 %************************************************************************
132 %*                                                                      *
133 \subsection{Simple Id construction}
134 %*                                                                      *
135 %************************************************************************
136
137 Absolutely all Ids are made by mkId.  It is just like Var.mkId,
138 but in addition it pins free-tyvar-info onto the Id's type, 
139 where it can easily be found.
140
141 \begin{code}
142 mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id
143 mkLocalIdWithInfo name ty info = Var.mkLocalId name (addFreeTyVars ty) info
144
145 mkSpecPragmaId :: Name -> Type -> Id
146 mkSpecPragmaId name ty = Var.mkSpecPragmaId name (addFreeTyVars ty) vanillaIdInfo
147
148 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
149 mkGlobalId details name ty info = Var.mkGlobalId details name (addFreeTyVars ty) info
150 \end{code}
151
152 \begin{code}
153 mkLocalId :: Name -> Type -> Id
154 mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo
155
156 -- SysLocal: for an Id being created by the compiler out of thin air...
157 -- UserLocal: an Id with a name the user might recognize...
158 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
159 mkSysLocal  :: EncodedFS  -> Unique -> Type -> Id
160 mkVanillaGlobal :: Name -> Type -> IdInfo -> Id
161
162 -- for SysLocal, we assume the base name is already encoded, to avoid
163 -- re-encoding the same string over and over again.
164 mkSysLocal          fs uniq ty = mkLocalId (mkSystemNameEncoded uniq fs) ty
165
166 -- version to use when the faststring needs to be encoded
167 mkSysLocalUnencoded fs uniq ty = mkLocalId (mkSystemName uniq fs)        ty
168
169 mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName    uniq occ loc) ty
170 mkVanillaGlobal             = mkGlobalId VanillaGlobal
171 \end{code}
172
173 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
174 @Uniques@, but that's OK because the templates are supposed to be
175 instantiated before use.
176  
177 \begin{code}
178 -- "Wild Id" typically used when you need a binder that you don't expect to use
179 mkWildId :: Type -> Id
180 mkWildId ty = mkSysLocal FSLIT("wild") (mkBuiltinUnique 1) ty
181
182 mkWorkerId :: Unique -> Id -> Type -> Id
183 -- A worker gets a local name.  CoreTidy will externalise it if necessary.
184 mkWorkerId uniq unwrkr ty
185   = mkLocalId wkr_name ty
186   where
187     wkr_name = mkInternalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcLoc unwrkr)
188
189 -- "Template locals" typically used in unfoldings
190 mkTemplateLocals :: [Type] -> [Id]
191 mkTemplateLocals tys = zipWith mkTemplateLocal [1..] tys
192
193 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
194 -- The Int gives the starting point for unique allocation
195 mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys
196
197 mkTemplateLocal :: Int -> Type -> Id
198 mkTemplateLocal i ty = mkSysLocal FSLIT("tpl") (mkBuiltinUnique i) ty
199 \end{code}
200
201
202 %************************************************************************
203 %*                                                                      *
204 \subsection[Id-general-funs]{General @Id@-related functions}
205 %*                                                                      *
206 %************************************************************************
207
208 \begin{code}
209 setIdType :: Id -> Type -> Id
210         -- Add free tyvar info to the type
211 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
212
213 idPrimRep :: Id -> PrimRep
214 idPrimRep id = typePrimRep (idType id)
215 \end{code}
216
217
218 %************************************************************************
219 %*                                                                      *
220 \subsection{Special Ids}
221 %*                                                                      *
222 %************************************************************************
223
224 The @SpecPragmaId@ exists only to make Ids that are
225 on the *LHS* of bindings created by SPECIALISE pragmas; 
226 eg:             s = f Int d
227 The SpecPragmaId is never itself mentioned; it
228 exists solely so that the specialiser will find
229 the call to f, and make specialised version of it.
230 The SpecPragmaId binding is discarded by the specialiser
231 when it gathers up overloaded calls.
232 Meanwhile, it is not discarded as dead code.
233
234
235 \begin{code}
236 recordSelectorFieldLabel :: Id -> FieldLabel
237 recordSelectorFieldLabel id = case globalIdDetails id of
238                                  RecordSelId lbl -> lbl
239
240 isRecordSelector id = case globalIdDetails id of
241                         RecordSelId lbl -> True
242                         other           -> False
243
244 isPrimOpId id = case globalIdDetails id of
245                     PrimOpId op -> True
246                     other       -> False
247
248 isPrimOpId_maybe id = case globalIdDetails id of
249                             PrimOpId op -> Just op
250                             other       -> Nothing
251
252 isFCallId id = case globalIdDetails id of
253                     FCallId call -> True
254                     other        -> False
255
256 isFCallId_maybe id = case globalIdDetails id of
257                             FCallId call -> Just call
258                             other        -> Nothing
259
260 isDataConWorkId id = case globalIdDetails id of
261                         DataConWorkId _ -> True
262                         other           -> False
263
264 isDataConWorkId_maybe id = case globalIdDetails id of
265                           DataConWorkId con -> Just con
266                           other             -> Nothing
267
268 isDataConWrapId_maybe id = case globalIdDetails id of
269                                   DataConWrapId con -> Just con
270                                   other             -> Nothing
271
272 isDataConWrapId id = case globalIdDetails id of
273                         DataConWrapId con -> True
274                         other             -> False
275
276 -- hasNoBinding returns True of an Id which may not have a
277 -- binding, even though it is defined in this module.  
278 -- Data constructor workers used to be things of this kind, but
279 -- they aren't any more.  Instead, we inject a binding for 
280 -- them at the CorePrep stage. 
281 -- EXCEPT: unboxed tuples, which definitely have no binding
282 hasNoBinding id = case globalIdDetails id of
283                         PrimOpId _       -> True
284                         FCallId _        -> True
285                         DataConWorkId dc -> isUnboxedTupleCon dc
286                         other            -> False
287
288 isImplicitId :: Id -> Bool
289         -- isImplicitId tells whether an Id's info is implied by other
290         -- declarations, so we don't need to put its signature in an interface
291         -- file, even if it's mentioned in some other interface unfolding.
292 isImplicitId id
293   = case globalIdDetails id of
294         RecordSelId _   -> True
295         FCallId _       -> True
296         PrimOpId _      -> True
297         ClassOpId _     -> True
298         GenericOpId _   -> True
299         DataConWorkId _ -> True
300         DataConWrapId _ -> True
301                 -- These are are implied by their type or class decl;
302                 -- remember that all type and class decls appear in the interface file.
303                 -- The dfun id is not an implicit Id; it must *not* be omitted, because 
304                 -- it carries version info for the instance decl
305         other           -> False
306 \end{code}
307
308 \begin{code}
309 isDeadBinder :: Id -> Bool
310 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
311                   | otherwise = False   -- TyVars count as not dead
312 \end{code}
313
314
315 %************************************************************************
316 %*                                                                      *
317 \subsection{IdInfo stuff}
318 %*                                                                      *
319 %************************************************************************
320
321 \begin{code}
322         ---------------------------------
323         -- ARITY
324 idArity :: Id -> Arity
325 idArity id = arityInfo (idInfo id)
326
327 setIdArity :: Id -> Arity -> Id
328 setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id
329
330 #ifdef OLD_STRICTNESS
331         ---------------------------------
332         -- (OLD) STRICTNESS 
333 idStrictness :: Id -> StrictnessInfo
334 idStrictness id = strictnessInfo (idInfo id)
335
336 setIdStrictness :: Id -> StrictnessInfo -> Id
337 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
338 #endif
339
340 -- isBottomingId returns true if an application to n args would diverge
341 isBottomingId :: Id -> Bool
342 isBottomingId id = isBottomingSig (idNewStrictness id)
343
344 idNewStrictness_maybe :: Id -> Maybe StrictSig
345 idNewStrictness :: Id -> StrictSig
346
347 idNewStrictness_maybe id = newStrictnessInfo (idInfo id)
348 idNewStrictness       id = idNewStrictness_maybe id `orElse` topSig
349
350 setIdNewStrictness :: Id -> StrictSig -> Id
351 setIdNewStrictness id sig = modifyIdInfo (`setNewStrictnessInfo` Just sig) id
352
353 zapIdNewStrictness :: Id -> Id
354 zapIdNewStrictness id = modifyIdInfo (`setNewStrictnessInfo` Nothing) id
355
356         ---------------------------------
357         -- WORKER ID
358 idWorkerInfo :: Id -> WorkerInfo
359 idWorkerInfo id = workerInfo (idInfo id)
360
361 setIdWorkerInfo :: Id -> WorkerInfo -> Id
362 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
363
364         ---------------------------------
365         -- UNFOLDING
366 idUnfolding :: Id -> Unfolding
367 idUnfolding id = unfoldingInfo (idInfo id)
368
369 setIdUnfolding :: Id -> Unfolding -> Id
370 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
371
372 #ifdef OLD_STRICTNESS
373         ---------------------------------
374         -- (OLD) DEMAND
375 idDemandInfo :: Id -> Demand.Demand
376 idDemandInfo id = demandInfo (idInfo id)
377
378 setIdDemandInfo :: Id -> Demand.Demand -> Id
379 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
380 #endif
381
382 idNewDemandInfo_maybe :: Id -> Maybe NewDemand.Demand
383 idNewDemandInfo       :: Id -> NewDemand.Demand
384
385 idNewDemandInfo_maybe id = newDemandInfo (idInfo id)
386 idNewDemandInfo       id = newDemandInfo (idInfo id) `orElse` NewDemand.topDmd
387
388 setIdNewDemandInfo :: Id -> NewDemand.Demand -> Id
389 setIdNewDemandInfo id dmd = modifyIdInfo (`setNewDemandInfo` Just dmd) id
390
391         ---------------------------------
392         -- SPECIALISATION
393 idSpecialisation :: Id -> CoreRules
394 idSpecialisation id = specInfo (idInfo id)
395
396 idCoreRules :: Id -> [IdCoreRule]
397 idCoreRules id = [(id,rule) | rule <- rulesRules (idSpecialisation id)]
398
399 setIdSpecialisation :: Id -> CoreRules -> Id
400 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
401
402         ---------------------------------
403         -- CAF INFO
404 idCafInfo :: Id -> CafInfo
405 #ifdef OLD_STRICTNESS
406 idCafInfo id = case cgInfo (idInfo id) of
407                   NoCgInfo -> pprPanic "idCafInfo" (ppr id)
408                   info     -> cgCafInfo info
409 #else
410 idCafInfo id = cafInfo (idInfo id)
411 #endif
412
413 setIdCafInfo :: Id -> CafInfo -> Id
414 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
415
416         ---------------------------------
417         -- CPR INFO
418 #ifdef OLD_STRICTNESS
419 idCprInfo :: Id -> CprInfo
420 idCprInfo id = cprInfo (idInfo id)
421
422 setIdCprInfo :: Id -> CprInfo -> Id
423 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
424 #endif
425
426         ---------------------------------
427         -- Occcurrence INFO
428 idOccInfo :: Id -> OccInfo
429 idOccInfo id = occInfo (idInfo id)
430
431 setIdOccInfo :: Id -> OccInfo -> Id
432 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
433 \end{code}
434
435
436         ---------------------------------
437         -- INLINING
438 The inline pragma tells us to be very keen to inline this Id, but it's still
439 OK not to if optimisation is switched off.
440
441 \begin{code}
442 idInlinePragma :: Id -> InlinePragInfo
443 idInlinePragma id = inlinePragInfo (idInfo id)
444
445 setInlinePragma :: Id -> InlinePragInfo -> Id
446 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
447
448 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
449 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
450 \end{code}
451
452
453         ---------------------------------
454         -- ONE-SHOT LAMBDAS
455 \begin{code}
456 idLBVarInfo :: Id -> LBVarInfo
457 idLBVarInfo id = lbvarInfo (idInfo id)
458
459 isOneShotLambda :: Id -> Bool
460 isOneShotLambda id = case idLBVarInfo id of
461                        IsOneShotLambda  -> True
462                        NoLBVarInfo      -> False
463
464 setOneShotLambda :: Id -> Id
465 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
466
467 clearOneShotLambda :: Id -> Id
468 clearOneShotLambda id 
469   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
470   | otherwise          = id                     
471
472 -- But watch out: this may change the type of something else
473 --      f = \x -> e
474 -- If we change the one-shot-ness of x, f's type changes
475 \end{code}
476
477 \begin{code}
478 zapLamIdInfo :: Id -> Id
479 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
480
481 zapDemandIdInfo id = maybeModifyIdInfo zapDemandInfo id
482 \end{code}
483