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