[project @ 2002-04-04 13:15:18 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, 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 OLD_STRICTNESS
56         idDemandInfo, 
57         idStrictness, 
58         idCprInfo,
59         setIdStrictness, 
60         setIdDemandInfo, 
61         setIdCprInfo,
62 #endif
63
64         idArity, 
65         idNewDemandInfo, idNewDemandInfo_maybe,
66         idNewStrictness, idNewStrictness_maybe, 
67         idTyGenInfo,
68         idWorkerInfo,
69         idUnfolding,
70         idSpecialisation, idCoreRules,
71         idCgInfo,
72         idCafInfo,
73         idLBVarInfo,
74         idOccInfo,
75
76 #ifdef OLD_STRICTNESS
77         newStrictnessFromOld    -- Temporary
78 #endif
79
80     ) where
81
82 #include "HsVersions.h"
83
84
85 import CoreSyn          ( Unfolding, CoreRules, IdCoreRule, rulesRules )
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, topDmd, topSig, isBottomingSig )
103 import Name             ( Name, OccName,
104                           mkSystemName, mkInternalName,
105                           getOccName, getSrcLoc
106                         ) 
107 import OccName          ( EncodedFS, 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 OLD_STRICTNESS
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  :: EncodedFS  -> Unique -> Type -> Id
164 mkVanillaGlobal :: Name -> Type -> IdInfo -> Id
165
166 -- for SysLocal, we assume the base name is already encoded, to avoid
167 -- re-encoding the same string over and over again.
168 mkSysLocal  fs uniq ty      = mkLocalId (mkSystemName uniq fs)      ty
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 isDataConId id = case globalIdDetails id of
261                         DataConId _ -> True
262                         other       -> False
263
264 isDataConId_maybe id = case globalIdDetails id of
265                           DataConId 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 hasNoBinding id = case globalIdDetails id of
282                         PrimOpId _  -> True
283                         FCallId _   -> True
284                         other       -> False
285
286 isImplicitId :: Id -> Bool
287         -- isImplicitId tells whether an Id's info is implied by other
288         -- declarations, so we don't need to put its signature in an interface
289         -- file, even if it's mentioned in some other interface unfolding.
290 isImplicitId id
291   = case globalIdDetails id of
292         RecordSelId _   -> True -- Includes dictionary selectors
293         FCallId _       -> True
294         PrimOpId _      -> True
295         DataConId _     -> True
296         DataConWrapId _ -> True
297                 -- These are are implied by their type or class decl;
298                 -- remember that all type and class decls appear in the interface file.
299                 -- The dfun id must *not* be omitted, because it carries version info for
300                 -- the instance decl
301         other           -> False
302 \end{code}
303
304 \begin{code}
305 isDeadBinder :: Id -> Bool
306 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
307                   | otherwise = False   -- TyVars count as not dead
308 \end{code}
309
310
311 %************************************************************************
312 %*                                                                      *
313 \subsection{IdInfo stuff}
314 %*                                                                      *
315 %************************************************************************
316
317 \begin{code}
318         ---------------------------------
319         -- ARITY
320 idArity :: Id -> Arity
321 idArity id = arityInfo (idInfo id)
322
323 setIdArity :: Id -> Arity -> Id
324 setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id
325
326 #ifdef OLD_STRICTNESS
327         ---------------------------------
328         -- (OLD) STRICTNESS 
329 idStrictness :: Id -> StrictnessInfo
330 idStrictness id = strictnessInfo (idInfo id)
331
332 setIdStrictness :: Id -> StrictnessInfo -> Id
333 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
334 #endif
335
336 -- isBottomingId returns true if an application to n args would diverge
337 isBottomingId :: Id -> Bool
338 isBottomingId id = isBottomingSig (idNewStrictness id)
339
340 idNewStrictness_maybe :: Id -> Maybe StrictSig
341 idNewStrictness :: Id -> StrictSig
342
343 idNewStrictness_maybe id = newStrictnessInfo (idInfo id)
344 idNewStrictness       id = idNewStrictness_maybe id `orElse` topSig
345
346 setIdNewStrictness :: Id -> StrictSig -> Id
347 setIdNewStrictness id sig = modifyIdInfo (`setNewStrictnessInfo` Just sig) id
348
349 zapIdNewStrictness :: Id -> Id
350 zapIdNewStrictness id = modifyIdInfo (`setNewStrictnessInfo` Nothing) id
351
352         ---------------------------------
353         -- TYPE GENERALISATION
354 idTyGenInfo :: Id -> TyGenInfo
355 idTyGenInfo id = tyGenInfo (idInfo id)
356
357 setIdTyGenInfo :: Id -> TyGenInfo -> Id
358 setIdTyGenInfo id tygen_info = modifyIdInfo (`setTyGenInfo` tygen_info) id
359
360         ---------------------------------
361         -- WORKER ID
362 idWorkerInfo :: Id -> WorkerInfo
363 idWorkerInfo id = workerInfo (idInfo id)
364
365 setIdWorkerInfo :: Id -> WorkerInfo -> Id
366 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
367
368         ---------------------------------
369         -- UNFOLDING
370 idUnfolding :: Id -> Unfolding
371 idUnfolding id = unfoldingInfo (idInfo id)
372
373 setIdUnfolding :: Id -> Unfolding -> Id
374 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
375
376 #ifdef OLD_STRICTNESS
377         ---------------------------------
378         -- (OLD) DEMAND
379 idDemandInfo :: Id -> Demand.Demand
380 idDemandInfo id = demandInfo (idInfo id)
381
382 setIdDemandInfo :: Id -> Demand.Demand -> Id
383 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
384 #endif
385
386 idNewDemandInfo_maybe :: Id -> Maybe NewDemand.Demand
387 idNewDemandInfo       :: Id -> NewDemand.Demand
388
389 idNewDemandInfo_maybe id = newDemandInfo (idInfo id)
390 idNewDemandInfo       id = newDemandInfo (idInfo id) `orElse` NewDemand.topDmd
391
392 setIdNewDemandInfo :: Id -> NewDemand.Demand -> Id
393 setIdNewDemandInfo id dmd = modifyIdInfo (`setNewDemandInfo` Just dmd) id
394
395         ---------------------------------
396         -- SPECIALISATION
397 idSpecialisation :: Id -> CoreRules
398 idSpecialisation id = specInfo (idInfo id)
399
400 idCoreRules :: Id -> [IdCoreRule]
401 idCoreRules id = [(id,rule) | rule <- rulesRules (idSpecialisation id)]
402
403 setIdSpecialisation :: Id -> CoreRules -> Id
404 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
405
406         ---------------------------------
407         -- CG INFO
408 idCgInfo :: Id -> CgInfo
409 #ifdef OLD_STRICTNESS
410 idCgInfo id = case cgInfo (idInfo id) of
411                   NoCgInfo -> pprPanic "idCgInfo" (ppr id)
412                   info     -> info
413 #else
414 idCgInfo id = cgInfo (idInfo id)
415 #endif          
416
417 setIdCgInfo :: Id -> CgInfo -> Id
418 setIdCgInfo id cg_info = modifyIdInfo (`setCgInfo` cg_info) id
419
420         ---------------------------------
421         -- CAF INFO
422 idCafInfo :: Id -> CafInfo
423 #ifdef OLD_STRICTNESS
424 idCafInfo id = case cgInfo (idInfo id) of
425                   NoCgInfo -> pprPanic "idCafInfo" (ppr id)
426                   info     -> cgCafInfo info
427 #else
428 idCafInfo id = cgCafInfo (idCgInfo id)
429 #endif
430         ---------------------------------
431         -- CPR INFO
432 #ifdef OLD_STRICTNESS
433 idCprInfo :: Id -> CprInfo
434 idCprInfo id = cprInfo (idInfo id)
435
436 setIdCprInfo :: Id -> CprInfo -> Id
437 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
438 #endif
439
440         ---------------------------------
441         -- Occcurrence INFO
442 idOccInfo :: Id -> OccInfo
443 idOccInfo id = occInfo (idInfo id)
444
445 setIdOccInfo :: Id -> OccInfo -> Id
446 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
447 \end{code}
448
449
450         ---------------------------------
451         -- INLINING
452 The inline pragma tells us to be very keen to inline this Id, but it's still
453 OK not to if optimisation is switched off.
454
455 \begin{code}
456 idInlinePragma :: Id -> InlinePragInfo
457 idInlinePragma id = inlinePragInfo (idInfo id)
458
459 setInlinePragma :: Id -> InlinePragInfo -> Id
460 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
461
462 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
463 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
464 \end{code}
465
466
467         ---------------------------------
468         -- ONE-SHOT LAMBDAS
469 \begin{code}
470 idLBVarInfo :: Id -> LBVarInfo
471 idLBVarInfo id = lbvarInfo (idInfo id)
472
473 isOneShotLambda :: Id -> Bool
474 isOneShotLambda id = analysis || hack
475   where analysis = case idLBVarInfo id of
476                      LBVarInfo u    | u `eqUsage` usOnce      -> True
477                      other                                    -> False
478         hack     = case splitTyConApp_maybe (idType id) of
479                      Just (tycon,_) | tycon == statePrimTyCon -> True
480                      other                                    -> False
481
482         -- The last clause is a gross hack.  It claims that 
483         -- every function over realWorldStatePrimTy is a one-shot
484         -- function.  This is pretty true in practice, and makes a big
485         -- difference.  For example, consider
486         --      a `thenST` \ r -> ...E...
487         -- The early full laziness pass, if it doesn't know that r is one-shot
488         -- will pull out E (let's say it doesn't mention r) to give
489         --      let lvl = E in a `thenST` \ r -> ...lvl...
490         -- When `thenST` gets inlined, we end up with
491         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
492         -- and we don't re-inline E.
493         --
494         -- It would be better to spot that r was one-shot to start with, but
495         -- I don't want to rely on that.
496         --
497         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
498         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
499
500 setOneShotLambda :: Id -> Id
501 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` LBVarInfo usOnce) id
502
503 clearOneShotLambda :: Id -> Id
504 clearOneShotLambda id 
505   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
506   | otherwise          = id                     
507
508 -- But watch out: this may change the type of something else
509 --      f = \x -> e
510 -- If we change the one-shot-ness of x, f's type changes
511 \end{code}
512
513 \begin{code}
514 zapLamIdInfo :: Id -> Id
515 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
516
517 zapDemandIdInfo id = maybeModifyIdInfo zapDemandInfo id
518 \end{code}
519