[project @ 2001-12-10 14:07:30 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, 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         isDataConId, isDataConId_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         setIdTyGenInfo,
50         setIdWorkerInfo,
51         setIdSpecialisation,
52         setIdCgInfo,
53         setIdOccInfo,
54
55 #ifdef DEBUG
56         idDemandInfo, 
57         idStrictness, 
58         idCprInfo,
59         setIdStrictness, 
60         setIdDemandInfo, 
61         setIdCprInfo,
62 #endif
63
64         idArity, 
65         idNewDemandInfo,
66         idNewStrictness, idNewStrictness_maybe, 
67         idTyGenInfo,
68         idWorkerInfo,
69         idUnfolding,
70         idSpecialisation,
71         idCgInfo,
72         idCafInfo,
73         idLBVarInfo,
74         idOccInfo,
75
76 #ifdef DEBUG
77         newStrictnessFromOld    -- Temporary
78 #endif
79
80     ) where
81
82 #include "HsVersions.h"
83
84
85 import CoreSyn          ( Unfolding, CoreRules )
86 import BasicTypes       ( Arity )
87 import Var              ( Id, DictId,
88                           isId, isExportedId, isSpecPragmaId, isLocalId,
89                           idName, idType, idUnique, idInfo, isGlobalId,
90                           setIdName, setVarType, setIdUnique, setIdLocalExported,
91                           setIdInfo, lazySetIdInfo, modifyIdInfo, 
92                           maybeModifyIdInfo,
93                           globalIdDetails, setGlobalIdDetails
94                         )
95 import qualified Var    ( mkLocalId, mkGlobalId, mkSpecPragmaId )
96 import Type             ( Type, typePrimRep, addFreeTyVars, 
97                           usOnce, eqUsage, seqType, splitTyConApp_maybe )
98
99 import IdInfo 
100
101 import qualified Demand ( Demand )
102 import NewDemand        ( Demand, StrictSig, topSig, isBottomingSig )
103 import Name             ( Name, OccName,
104                           mkSysLocalName, mkLocalName,
105                           getOccName, getSrcLoc
106                         ) 
107 import OccName          ( UserFS, mkWorkerOcc )
108 import PrimRep          ( PrimRep )
109 import TysPrim          ( statePrimTyCon )
110 import FieldLabel       ( FieldLabel )
111 import Maybes           ( orElse )
112 import SrcLoc           ( SrcLoc )
113 import Outputable
114 import Unique           ( Unique, mkBuiltinUnique )
115
116 -- infixl so you can say (id `set` a `set` b)
117 infixl  1 `setIdUnfolding`,
118           `setIdArity`,
119           `setIdNewDemandInfo`,
120           `setIdNewStrictness`,
121           `setIdTyGenInfo`,
122           `setIdWorkerInfo`,
123           `setIdSpecialisation`,
124           `setInlinePragma`,
125           `idCafInfo`
126 #ifdef DEBUG
127           ,`idCprInfo`
128           ,`setIdStrictness`
129           ,`setIdDemandInfo`
130 #endif
131 \end{code}
132
133
134
135 %************************************************************************
136 %*                                                                      *
137 \subsection{Simple Id construction}
138 %*                                                                      *
139 %************************************************************************
140
141 Absolutely all Ids are made by mkId.  It is just like Var.mkId,
142 but in addition it pins free-tyvar-info onto the Id's type, 
143 where it can easily be found.
144
145 \begin{code}
146 mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id
147 mkLocalIdWithInfo name ty info = Var.mkLocalId name (addFreeTyVars ty) info
148
149 mkSpecPragmaId :: Name -> Type -> Id
150 mkSpecPragmaId name ty = Var.mkSpecPragmaId name (addFreeTyVars ty) vanillaIdInfo
151
152 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
153 mkGlobalId details name ty info = Var.mkGlobalId details name (addFreeTyVars ty) info
154 \end{code}
155
156 \begin{code}
157 mkLocalId :: Name -> Type -> Id
158 mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo
159
160 -- SysLocal: for an Id being created by the compiler out of thin air...
161 -- UserLocal: an Id with a name the user might recognize...
162 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
163 mkSysLocal  :: UserFS  -> Unique -> Type -> Id
164 mkVanillaGlobal :: Name -> Type -> IdInfo -> Id
165
166 mkSysLocal  fs uniq ty      = mkLocalId (mkSysLocalName uniq fs)      ty
167 mkUserLocal occ uniq ty loc = mkLocalId (mkLocalName    uniq occ loc) ty
168 mkVanillaGlobal             = mkGlobalId VanillaGlobal
169 \end{code}
170
171 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
172 @Uniques@, but that's OK because the templates are supposed to be
173 instantiated before use.
174  
175 \begin{code}
176 -- "Wild Id" typically used when you need a binder that you don't expect to use
177 mkWildId :: Type -> Id
178 mkWildId ty = mkSysLocal SLIT("wild") (mkBuiltinUnique 1) ty
179
180 mkWorkerId :: Unique -> Id -> Type -> Id
181 -- A worker gets a local name.  CoreTidy will globalise it if necessary.
182 mkWorkerId uniq unwrkr ty
183   = mkLocalId wkr_name ty
184   where
185     wkr_name = mkLocalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcLoc unwrkr)
186
187 -- "Template locals" typically used in unfoldings
188 mkTemplateLocals :: [Type] -> [Id]
189 mkTemplateLocals tys = zipWith mkTemplateLocal [1..] tys
190
191 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
192 -- The Int gives the starting point for unique allocation
193 mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys
194
195 mkTemplateLocal :: Int -> Type -> Id
196 mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
197 \end{code}
198
199
200 %************************************************************************
201 %*                                                                      *
202 \subsection[Id-general-funs]{General @Id@-related functions}
203 %*                                                                      *
204 %************************************************************************
205
206 \begin{code}
207 setIdType :: Id -> Type -> Id
208         -- Add free tyvar info to the type
209 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
210
211 idPrimRep :: Id -> PrimRep
212 idPrimRep id = typePrimRep (idType id)
213 \end{code}
214
215
216 %************************************************************************
217 %*                                                                      *
218 \subsection{Special Ids}
219 %*                                                                      *
220 %************************************************************************
221
222 The @SpecPragmaId@ exists only to make Ids that are
223 on the *LHS* of bindings created by SPECIALISE pragmas; 
224 eg:             s = f Int d
225 The SpecPragmaId is never itself mentioned; it
226 exists solely so that the specialiser will find
227 the call to f, and make specialised version of it.
228 The SpecPragmaId binding is discarded by the specialiser
229 when it gathers up overloaded calls.
230 Meanwhile, it is not discarded as dead code.
231
232
233 \begin{code}
234 recordSelectorFieldLabel :: Id -> FieldLabel
235 recordSelectorFieldLabel id = case globalIdDetails id of
236                                  RecordSelId lbl -> lbl
237
238 isRecordSelector id = case globalIdDetails id of
239                         RecordSelId lbl -> True
240                         other           -> False
241
242 isPrimOpId id = case globalIdDetails id of
243                     PrimOpId op -> True
244                     other       -> False
245
246 isPrimOpId_maybe id = case globalIdDetails id of
247                             PrimOpId op -> Just op
248                             other       -> Nothing
249
250 isFCallId id = case globalIdDetails id of
251                     FCallId call -> True
252                     other        -> False
253
254 isFCallId_maybe id = case globalIdDetails id of
255                             FCallId call -> Just call
256                             other        -> Nothing
257
258 isDataConId id = case globalIdDetails id of
259                         DataConId _ -> True
260                         other       -> False
261
262 isDataConId_maybe id = case globalIdDetails id of
263                           DataConId con -> Just con
264                           other         -> Nothing
265
266 isDataConWrapId_maybe id = case globalIdDetails id of
267                                   DataConWrapId con -> Just con
268                                   other             -> Nothing
269
270 isDataConWrapId id = case globalIdDetails id of
271                         DataConWrapId con -> True
272                         other             -> False
273
274 -- hasNoBinding returns True of an Id which may not have a
275 -- binding, even though it is defined in this module.  
276 -- Data constructor workers used to be things of this kind, but
277 -- they aren't any more.  Instead, we inject a binding for 
278 -- them at the CorePrep stage.
279 hasNoBinding id = case globalIdDetails id of
280                         PrimOpId _  -> True
281                         FCallId _   -> True
282                         other       -> False
283
284 isImplicitId :: Id -> Bool
285         -- isImplicitId tells whether an Id's info is implied by other
286         -- declarations, so we don't need to put its signature in an interface
287         -- file, even if it's mentioned in some other interface unfolding.
288 isImplicitId id
289   = case globalIdDetails id of
290         RecordSelId _   -> True -- Includes dictionary selectors
291         FCallId _       -> True
292         PrimOpId _      -> True
293         DataConId _     -> True
294         DataConWrapId _ -> True
295                 -- These are are implied by their type or class decl;
296                 -- remember that all type and class decls appear in the interface file.
297                 -- The dfun id must *not* be omitted, because it carries version info for
298                 -- the instance decl
299         other           -> False
300 \end{code}
301
302 \begin{code}
303 isDeadBinder :: Id -> Bool
304 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
305                   | otherwise = False   -- TyVars count as not dead
306 \end{code}
307
308
309 %************************************************************************
310 %*                                                                      *
311 \subsection{IdInfo stuff}
312 %*                                                                      *
313 %************************************************************************
314
315 \begin{code}
316         ---------------------------------
317         -- ARITY
318 idArity :: Id -> Arity
319 idArity id = arityInfo (idInfo id)
320
321 setIdArity :: Id -> Arity -> Id
322 setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id
323
324 #ifdef DEBUG
325         ---------------------------------
326         -- (OLD) STRICTNESS 
327 idStrictness :: Id -> StrictnessInfo
328 idStrictness id = strictnessInfo (idInfo id)
329
330 setIdStrictness :: Id -> StrictnessInfo -> Id
331 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
332 #endif
333
334 -- isBottomingId returns true if an application to n args would diverge
335 isBottomingId :: Id -> Bool
336 isBottomingId id = isBottomingSig (idNewStrictness id)
337
338 idNewStrictness_maybe :: Id -> Maybe StrictSig
339 idNewStrictness :: Id -> StrictSig
340
341 idNewStrictness_maybe id = newStrictnessInfo (idInfo id)
342 idNewStrictness       id = idNewStrictness_maybe id `orElse` topSig
343
344 setIdNewStrictness :: Id -> StrictSig -> Id
345 setIdNewStrictness id sig = modifyIdInfo (`setNewStrictnessInfo` Just sig) id
346
347 zapIdNewStrictness :: Id -> Id
348 zapIdNewStrictness id = modifyIdInfo (`setNewStrictnessInfo` Nothing) id
349
350         ---------------------------------
351         -- TYPE GENERALISATION
352 idTyGenInfo :: Id -> TyGenInfo
353 idTyGenInfo id = tyGenInfo (idInfo id)
354
355 setIdTyGenInfo :: Id -> TyGenInfo -> Id
356 setIdTyGenInfo id tygen_info = modifyIdInfo (`setTyGenInfo` tygen_info) 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 DEBUG
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 :: Id -> NewDemand.Demand
385 idNewDemandInfo id = newDemandInfo (idInfo id)
386
387 setIdNewDemandInfo :: Id -> NewDemand.Demand -> Id
388 setIdNewDemandInfo id dmd = modifyIdInfo (`setNewDemandInfo` dmd) id
389
390         ---------------------------------
391         -- SPECIALISATION
392 idSpecialisation :: Id -> CoreRules
393 idSpecialisation id = specInfo (idInfo id)
394
395 setIdSpecialisation :: Id -> CoreRules -> Id
396 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
397
398         ---------------------------------
399         -- CG INFO
400 idCgInfo :: Id -> CgInfo
401 #ifdef DEBUG
402 idCgInfo id = case cgInfo (idInfo id) of
403                   NoCgInfo -> pprPanic "idCgInfo" (ppr id)
404                   info     -> info
405 #else
406 idCgInfo id = cgInfo (idInfo id)
407 #endif          
408
409 setIdCgInfo :: Id -> CgInfo -> Id
410 setIdCgInfo id cg_info = modifyIdInfo (`setCgInfo` cg_info) id
411
412         ---------------------------------
413         -- CAF INFO
414 idCafInfo :: Id -> CafInfo
415 #ifdef DEBUG
416 idCafInfo id = case cgInfo (idInfo id) of
417                   NoCgInfo -> pprPanic "idCafInfo" (ppr id)
418                   info     -> cgCafInfo info
419 #else
420 idCafInfo id = cgCafInfo (idCgInfo id)
421 #endif
422         ---------------------------------
423         -- CPR INFO
424 #ifdef DEBUG
425 idCprInfo :: Id -> CprInfo
426 idCprInfo id = cprInfo (idInfo id)
427
428 setIdCprInfo :: Id -> CprInfo -> Id
429 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
430 #endif
431
432         ---------------------------------
433         -- Occcurrence INFO
434 idOccInfo :: Id -> OccInfo
435 idOccInfo id = occInfo (idInfo id)
436
437 setIdOccInfo :: Id -> OccInfo -> Id
438 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
439 \end{code}
440
441
442         ---------------------------------
443         -- INLINING
444 The inline pragma tells us to be very keen to inline this Id, but it's still
445 OK not to if optimisation is switched off.
446
447 \begin{code}
448 idInlinePragma :: Id -> InlinePragInfo
449 idInlinePragma id = inlinePragInfo (idInfo id)
450
451 setInlinePragma :: Id -> InlinePragInfo -> Id
452 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
453
454 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
455 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
456 \end{code}
457
458
459         ---------------------------------
460         -- ONE-SHOT LAMBDAS
461 \begin{code}
462 idLBVarInfo :: Id -> LBVarInfo
463 idLBVarInfo id = lbvarInfo (idInfo id)
464
465 isOneShotLambda :: Id -> Bool
466 isOneShotLambda id = analysis || hack
467   where analysis = case idLBVarInfo id of
468                      LBVarInfo u    | u `eqUsage` usOnce      -> True
469                      other                                    -> False
470         hack     = case splitTyConApp_maybe (idType id) of
471                      Just (tycon,_) | tycon == statePrimTyCon -> True
472                      other                                    -> False
473
474         -- The last clause is a gross hack.  It claims that 
475         -- every function over realWorldStatePrimTy is a one-shot
476         -- function.  This is pretty true in practice, and makes a big
477         -- difference.  For example, consider
478         --      a `thenST` \ r -> ...E...
479         -- The early full laziness pass, if it doesn't know that r is one-shot
480         -- will pull out E (let's say it doesn't mention r) to give
481         --      let lvl = E in a `thenST` \ r -> ...lvl...
482         -- When `thenST` gets inlined, we end up with
483         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
484         -- and we don't re-inline E.
485         --
486         -- It would be better to spot that r was one-shot to start with, but
487         -- I don't want to rely on that.
488         --
489         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
490         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
491
492 setOneShotLambda :: Id -> Id
493 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` LBVarInfo usOnce) id
494
495 clearOneShotLambda :: Id -> Id
496 clearOneShotLambda id 
497   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
498   | otherwise          = id                     
499
500 -- But watch out: this may change the type of something else
501 --      f = \x -> e
502 -- If we change the one-shot-ness of x, f's type changes
503 \end{code}
504
505 \begin{code}
506 zapLamIdInfo :: Id -> Id
507 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
508
509 zapDemandIdInfo id = maybeModifyIdInfo zapDemandInfo id
510 \end{code}
511