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