[project @ 2003-10-09 11:58:39 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         isBottomingId,
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         setIdArity,
46         setIdNewDemandInfo, 
47         setIdNewStrictness, zapIdNewStrictness,
48         setIdWorkerInfo,
49         setIdSpecialisation,
50         setIdCafInfo,
51         setIdOccInfo,
52
53 #ifdef OLD_STRICTNESS
54         idDemandInfo, 
55         idStrictness, 
56         idCprInfo,
57         setIdStrictness, 
58         setIdDemandInfo, 
59         setIdCprInfo,
60 #endif
61
62         idArity, 
63         idNewDemandInfo, idNewDemandInfo_maybe,
64         idNewStrictness, idNewStrictness_maybe, 
65         idWorkerInfo,
66         idUnfolding,
67         idSpecialisation, idCoreRules,
68         idCafInfo,
69         idLBVarInfo,
70         idOccInfo,
71
72 #ifdef OLD_STRICTNESS
73         newStrictnessFromOld    -- Temporary
74 #endif
75
76     ) where
77
78 #include "HsVersions.h"
79
80
81 import CoreSyn          ( Unfolding, CoreRules, IdCoreRule, rulesRules )
82 import BasicTypes       ( Arity )
83 import Var              ( Id, DictId,
84                           isId, isExportedId, isSpecPragmaId, isLocalId,
85                           idName, idType, idUnique, idInfo, isGlobalId,
86                           setIdName, setVarType, setIdUnique, setIdLocalExported,
87                           setIdInfo, lazySetIdInfo, modifyIdInfo, 
88                           maybeModifyIdInfo,
89                           globalIdDetails, setGlobalIdDetails
90                         )
91 import qualified Var    ( mkLocalId, mkGlobalId, mkSpecPragmaId )
92 import Type             ( Type, typePrimRep, addFreeTyVars, seqType)
93
94 import IdInfo 
95
96 #ifdef OLD_STRICTNESS
97 import qualified Demand ( Demand )
98 #endif
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                                  other -> panic "recordSelectorFieldLabel"
240
241 isRecordSelector id = case globalIdDetails id of
242                         RecordSelId lbl -> True
243                         other           -> False
244
245 isPrimOpId id = case globalIdDetails id of
246                     PrimOpId op -> True
247                     other       -> False
248
249 isPrimOpId_maybe id = case globalIdDetails id of
250                             PrimOpId op -> Just op
251                             other       -> Nothing
252
253 isFCallId id = case globalIdDetails id of
254                     FCallId call -> True
255                     other        -> False
256
257 isFCallId_maybe id = case globalIdDetails id of
258                             FCallId call -> Just call
259                             other        -> Nothing
260
261 isDataConWorkId id = case globalIdDetails id of
262                         DataConWorkId _ -> True
263                         other           -> False
264
265 isDataConWorkId_maybe id = case globalIdDetails id of
266                           DataConWorkId con -> Just con
267                           other             -> Nothing
268
269 -- hasNoBinding returns True of an Id which may not have a
270 -- binding, even though it is defined in this module.  
271 -- Data constructor workers used to be things of this kind, but
272 -- they aren't any more.  Instead, we inject a binding for 
273 -- them at the CorePrep stage. 
274 -- EXCEPT: unboxed tuples, which definitely have no binding
275 hasNoBinding id = case globalIdDetails id of
276                         PrimOpId _       -> True
277                         FCallId _        -> True
278                         DataConWorkId dc -> isUnboxedTupleCon dc
279                         other            -> False
280
281 isImplicitId :: Id -> Bool
282         -- isImplicitId tells whether an Id's info is implied by other
283         -- declarations, so we don't need to put its signature in an interface
284         -- file, even if it's mentioned in some other interface unfolding.
285 isImplicitId id
286   = case globalIdDetails id of
287         RecordSelId _   -> True
288         FCallId _       -> True
289         PrimOpId _      -> True
290         ClassOpId _     -> True
291         DataConWorkId _ -> True
292         DataConWrapId _ -> True
293                 -- These are are implied by their type or class decl;
294                 -- remember that all type and class decls appear in the interface file.
295                 -- The dfun id is not an implicit Id; it must *not* be omitted, because 
296                 -- it carries version info for the instance decl
297         other           -> False
298 \end{code}
299
300 \begin{code}
301 isDeadBinder :: Id -> Bool
302 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
303                   | otherwise = False   -- TyVars count as not dead
304 \end{code}
305
306
307 %************************************************************************
308 %*                                                                      *
309 \subsection{IdInfo stuff}
310 %*                                                                      *
311 %************************************************************************
312
313 \begin{code}
314         ---------------------------------
315         -- ARITY
316 idArity :: Id -> Arity
317 idArity id = arityInfo (idInfo id)
318
319 setIdArity :: Id -> Arity -> Id
320 setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id
321
322 #ifdef OLD_STRICTNESS
323         ---------------------------------
324         -- (OLD) STRICTNESS 
325 idStrictness :: Id -> StrictnessInfo
326 idStrictness id = strictnessInfo (idInfo id)
327
328 setIdStrictness :: Id -> StrictnessInfo -> Id
329 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
330 #endif
331
332 -- isBottomingId returns true if an application to n args would diverge
333 isBottomingId :: Id -> Bool
334 isBottomingId id = isBottomingSig (idNewStrictness id)
335
336 idNewStrictness_maybe :: Id -> Maybe StrictSig
337 idNewStrictness :: Id -> StrictSig
338
339 idNewStrictness_maybe id = newStrictnessInfo (idInfo id)
340 idNewStrictness       id = idNewStrictness_maybe id `orElse` topSig
341
342 setIdNewStrictness :: Id -> StrictSig -> Id
343 setIdNewStrictness id sig = modifyIdInfo (`setNewStrictnessInfo` Just sig) id
344
345 zapIdNewStrictness :: Id -> Id
346 zapIdNewStrictness id = modifyIdInfo (`setNewStrictnessInfo` Nothing) id
347
348         ---------------------------------
349         -- WORKER ID
350 idWorkerInfo :: Id -> WorkerInfo
351 idWorkerInfo id = workerInfo (idInfo id)
352
353 setIdWorkerInfo :: Id -> WorkerInfo -> Id
354 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
355
356         ---------------------------------
357         -- UNFOLDING
358 idUnfolding :: Id -> Unfolding
359 idUnfolding id = unfoldingInfo (idInfo id)
360
361 setIdUnfolding :: Id -> Unfolding -> Id
362 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
363
364 #ifdef OLD_STRICTNESS
365         ---------------------------------
366         -- (OLD) DEMAND
367 idDemandInfo :: Id -> Demand.Demand
368 idDemandInfo id = demandInfo (idInfo id)
369
370 setIdDemandInfo :: Id -> Demand.Demand -> Id
371 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
372 #endif
373
374 idNewDemandInfo_maybe :: Id -> Maybe NewDemand.Demand
375 idNewDemandInfo       :: Id -> NewDemand.Demand
376
377 idNewDemandInfo_maybe id = newDemandInfo (idInfo id)
378 idNewDemandInfo       id = newDemandInfo (idInfo id) `orElse` NewDemand.topDmd
379
380 setIdNewDemandInfo :: Id -> NewDemand.Demand -> Id
381 setIdNewDemandInfo id dmd = modifyIdInfo (`setNewDemandInfo` Just dmd) id
382
383         ---------------------------------
384         -- SPECIALISATION
385 idSpecialisation :: Id -> CoreRules
386 idSpecialisation id = specInfo (idInfo id)
387
388 idCoreRules :: Id -> [IdCoreRule]
389 idCoreRules id = [(id,rule) | rule <- rulesRules (idSpecialisation id)]
390
391 setIdSpecialisation :: Id -> CoreRules -> Id
392 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
393
394         ---------------------------------
395         -- CAF INFO
396 idCafInfo :: Id -> CafInfo
397 #ifdef OLD_STRICTNESS
398 idCafInfo id = case cgInfo (idInfo id) of
399                   NoCgInfo -> pprPanic "idCafInfo" (ppr id)
400                   info     -> cgCafInfo info
401 #else
402 idCafInfo id = cafInfo (idInfo id)
403 #endif
404
405 setIdCafInfo :: Id -> CafInfo -> Id
406 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
407
408         ---------------------------------
409         -- CPR INFO
410 #ifdef OLD_STRICTNESS
411 idCprInfo :: Id -> CprInfo
412 idCprInfo id = cprInfo (idInfo id)
413
414 setIdCprInfo :: Id -> CprInfo -> Id
415 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
416 #endif
417
418         ---------------------------------
419         -- Occcurrence INFO
420 idOccInfo :: Id -> OccInfo
421 idOccInfo id = occInfo (idInfo id)
422
423 setIdOccInfo :: Id -> OccInfo -> Id
424 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
425 \end{code}
426
427
428         ---------------------------------
429         -- INLINING
430 The inline pragma tells us to be very keen to inline this Id, but it's still
431 OK not to if optimisation is switched off.
432
433 \begin{code}
434 idInlinePragma :: Id -> InlinePragInfo
435 idInlinePragma id = inlinePragInfo (idInfo id)
436
437 setInlinePragma :: Id -> InlinePragInfo -> Id
438 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
439
440 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
441 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
442 \end{code}
443
444
445         ---------------------------------
446         -- ONE-SHOT LAMBDAS
447 \begin{code}
448 idLBVarInfo :: Id -> LBVarInfo
449 idLBVarInfo id = lbvarInfo (idInfo id)
450
451 isOneShotLambda :: Id -> Bool
452 isOneShotLambda id = case idLBVarInfo id of
453                        IsOneShotLambda  -> True
454                        NoLBVarInfo      -> False
455
456 setOneShotLambda :: Id -> Id
457 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
458
459 clearOneShotLambda :: Id -> Id
460 clearOneShotLambda id 
461   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
462   | otherwise          = id                     
463
464 -- But watch out: this may change the type of something else
465 --      f = \x -> e
466 -- If we change the one-shot-ness of x, f's type changes
467 \end{code}
468
469 \begin{code}
470 zapLamIdInfo :: Id -> Id
471 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
472
473 zapDemandIdInfo id = maybeModifyIdInfo zapDemandInfo id
474 \end{code}
475