[project @ 2005-04-28 10:09:41 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, mkExportedLocalId,
15
16         -- Taking an Id apart
17         idName, idType, idUnique, idInfo,
18         isId, globalIdDetails, idPrimRep,
19         recordSelectorFieldLabel,
20
21         -- Modifying an Id
22         setIdName, setIdUnique, Id.setIdType, setIdExported, setIdNotExported, 
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, idDataCon,
33         isBottomingId, idIsFrom,
34         hasNoBinding, 
35
36         -- Inline pragma stuff
37         idInlinePragma, setInlinePragma, modifyInlinePragma, 
38
39
40         -- One shot lambda stuff
41         isOneShotBndr, isOneShotLambda, isStateHackType,
42         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, CoreRule )
83 import BasicTypes       ( Arity )
84 import Var              ( Id, DictId,
85                           isId, isExportedId, isSpecPragmaId, isLocalId,
86                           idName, idType, idUnique, idInfo, isGlobalId,
87                           setIdName, setIdType, setIdUnique, 
88                           setIdExported, setIdNotExported,
89                           setIdInfo, lazySetIdInfo, modifyIdInfo, 
90                           maybeModifyIdInfo,
91                           globalIdDetails
92                         )
93 import qualified Var    ( mkLocalId, mkGlobalId, mkSpecPragmaId, mkExportedLocalId )
94 import TyCon            ( FieldLabel, TyCon )
95 import Type             ( Type, typePrimRep, addFreeTyVars, seqType, 
96                           splitTyConApp_maybe, PrimRep )
97 import TysPrim          ( statePrimTyCon )
98 import IdInfo 
99
100 #ifdef OLD_STRICTNESS
101 import qualified Demand ( Demand )
102 #endif
103 import DataCon          ( DataCon, isUnboxedTupleCon )
104 import NewDemand        ( Demand, StrictSig, topDmd, topSig, isBottomingSig )
105 import Name             ( Name, OccName, nameIsLocalOrFrom, 
106                           mkSystemVarName, mkSystemVarNameEncoded, mkInternalName,
107                           getOccName, getSrcLoc
108                         ) 
109 import Module           ( Module )
110 import OccName          ( EncodedFS, mkWorkerOcc )
111 import Maybes           ( orElse )
112 import SrcLoc           ( SrcLoc )
113 import Outputable
114 import Unique           ( Unique, mkBuiltinUnique )
115 import StaticFlags      ( opt_NoStateHack )
116
117 -- infixl so you can say (id `set` a `set` b)
118 infixl  1 `setIdUnfolding`,
119           `setIdArity`,
120           `setIdNewDemandInfo`,
121           `setIdNewStrictness`,
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 mkExportedLocalId :: Name -> Type -> Id
153 mkExportedLocalId name ty = Var.mkExportedLocalId name (addFreeTyVars ty) vanillaIdInfo
154
155 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
156 mkGlobalId details name ty info = Var.mkGlobalId details name (addFreeTyVars ty) info
157 \end{code}
158
159 \begin{code}
160 mkLocalId :: Name -> Type -> Id
161 mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo
162
163 -- SysLocal: for an Id being created by the compiler out of thin air...
164 -- UserLocal: an Id with a name the user might recognize...
165 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
166 mkSysLocal  :: EncodedFS  -> Unique -> Type -> Id
167 mkVanillaGlobal :: Name -> Type -> IdInfo -> Id
168
169 -- for SysLocal, we assume the base name is already encoded, to avoid
170 -- re-encoding the same string over and over again.
171 mkSysLocal fs uniq ty = mkLocalId (mkSystemVarNameEncoded uniq fs) ty
172
173 -- version to use when the faststring needs to be encoded
174 mkSysLocalUnencoded fs uniq ty = mkLocalId (mkSystemVarName uniq fs)  ty
175
176 mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName    uniq occ loc) ty
177 mkVanillaGlobal             = mkGlobalId VanillaGlobal
178 \end{code}
179
180 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
181 @Uniques@, but that's OK because the templates are supposed to be
182 instantiated before use.
183  
184 \begin{code}
185 -- "Wild Id" typically used when you need a binder that you don't expect to use
186 mkWildId :: Type -> Id
187 mkWildId ty = mkSysLocal FSLIT("wild") (mkBuiltinUnique 1) ty
188
189 mkWorkerId :: Unique -> Id -> Type -> Id
190 -- A worker gets a local name.  CoreTidy will externalise it if necessary.
191 mkWorkerId uniq unwrkr ty
192   = mkLocalId wkr_name ty
193   where
194     wkr_name = mkInternalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcLoc unwrkr)
195
196 -- "Template locals" typically used in unfoldings
197 mkTemplateLocals :: [Type] -> [Id]
198 mkTemplateLocals tys = zipWith mkTemplateLocal [1..] tys
199
200 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
201 -- The Int gives the starting point for unique allocation
202 mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys
203
204 mkTemplateLocal :: Int -> Type -> Id
205 mkTemplateLocal i ty = mkSysLocal FSLIT("tpl") (mkBuiltinUnique i) ty
206 \end{code}
207
208
209 %************************************************************************
210 %*                                                                      *
211 \subsection[Id-general-funs]{General @Id@-related functions}
212 %*                                                                      *
213 %************************************************************************
214
215 \begin{code}
216 setIdType :: Id -> Type -> Id
217         -- Add free tyvar info to the type
218 setIdType id ty = seqType ty `seq` Var.setIdType id (addFreeTyVars ty)
219
220 idPrimRep :: Id -> PrimRep
221 idPrimRep id = typePrimRep (idType id)
222 \end{code}
223
224
225 %************************************************************************
226 %*                                                                      *
227 \subsection{Special Ids}
228 %*                                                                      *
229 %************************************************************************
230
231 The @SpecPragmaId@ exists only to make Ids that are
232 on the *LHS* of bindings created by SPECIALISE pragmas; 
233 eg:             s = f Int d
234 The SpecPragmaId is never itself mentioned; it
235 exists solely so that the specialiser will find
236 the call to f, and make specialised version of it.
237 The SpecPragmaId binding is discarded by the specialiser
238 when it gathers up overloaded calls.
239 Meanwhile, it is not discarded as dead code.
240
241
242 \begin{code}
243 recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel)
244 recordSelectorFieldLabel id = case globalIdDetails id of
245                                  RecordSelId tycon lbl -> (tycon,lbl)
246                                  other -> panic "recordSelectorFieldLabel"
247
248 isRecordSelector id = case globalIdDetails id of
249                         RecordSelId _ _ -> True
250                         other           -> False
251
252 isPrimOpId id = case globalIdDetails id of
253                     PrimOpId op -> True
254                     other       -> False
255
256 isPrimOpId_maybe id = case globalIdDetails id of
257                             PrimOpId op -> Just op
258                             other       -> Nothing
259
260 isFCallId id = case globalIdDetails id of
261                     FCallId call -> True
262                     other        -> False
263
264 isFCallId_maybe id = case globalIdDetails id of
265                             FCallId call -> Just call
266                             other        -> Nothing
267
268 isDataConWorkId id = case globalIdDetails id of
269                         DataConWorkId _ -> True
270                         other           -> False
271
272 isDataConWorkId_maybe id = case globalIdDetails id of
273                           DataConWorkId con -> Just con
274                           other             -> Nothing
275
276 idDataCon :: Id -> DataCon
277 -- Get from either the worker or the wrapper to the DataCon
278 -- Currently used only in the desugarer
279 --       INVARIANT: idDataCon (dataConWrapId d) = d
280 -- (Remember, dataConWrapId can return either the wrapper or the worker.)
281 idDataCon id = case globalIdDetails id of
282                   DataConWorkId con -> con
283                   DataConWrapId con -> con
284                   other             -> pprPanic "idDataCon" (ppr id)
285
286
287 -- hasNoBinding returns True of an Id which may not have a
288 -- binding, even though it is defined in this module.  
289 -- Data constructor workers used to be things of this kind, but
290 -- they aren't any more.  Instead, we inject a binding for 
291 -- them at the CorePrep stage. 
292 -- EXCEPT: unboxed tuples, which definitely have no binding
293 hasNoBinding id = case globalIdDetails id of
294                         PrimOpId _       -> True
295                         FCallId _        -> True
296                         DataConWorkId dc -> isUnboxedTupleCon dc
297                         other            -> False
298
299 isImplicitId :: Id -> Bool
300         -- isImplicitId tells whether an Id's info is implied by other
301         -- declarations, so we don't need to put its signature in an interface
302         -- file, even if it's mentioned in some other interface unfolding.
303 isImplicitId id
304   = case globalIdDetails id of
305         RecordSelId _ _ -> True
306         FCallId _       -> True
307         PrimOpId _      -> True
308         ClassOpId _     -> True
309         DataConWorkId _ -> True
310         DataConWrapId _ -> True
311                 -- These are are implied by their type or class decl;
312                 -- remember that all type and class decls appear in the interface file.
313                 -- The dfun id is not an implicit Id; it must *not* be omitted, because 
314                 -- it carries version info for the instance decl
315         other           -> False
316
317 idIsFrom :: Module -> Id -> Bool
318 idIsFrom mod id = nameIsLocalOrFrom mod (idName id)
319 \end{code}
320
321 \begin{code}
322 isDeadBinder :: Id -> Bool
323 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
324                   | otherwise = False   -- TyVars count as not dead
325 \end{code}
326
327
328 %************************************************************************
329 %*                                                                      *
330 \subsection{IdInfo stuff}
331 %*                                                                      *
332 %************************************************************************
333
334 \begin{code}
335         ---------------------------------
336         -- ARITY
337 idArity :: Id -> Arity
338 idArity id = arityInfo (idInfo id)
339
340 setIdArity :: Id -> Arity -> Id
341 setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id
342
343 #ifdef OLD_STRICTNESS
344         ---------------------------------
345         -- (OLD) STRICTNESS 
346 idStrictness :: Id -> StrictnessInfo
347 idStrictness id = strictnessInfo (idInfo id)
348
349 setIdStrictness :: Id -> StrictnessInfo -> Id
350 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
351 #endif
352
353 -- isBottomingId returns true if an application to n args would diverge
354 isBottomingId :: Id -> Bool
355 isBottomingId id = isBottomingSig (idNewStrictness id)
356
357 idNewStrictness_maybe :: Id -> Maybe StrictSig
358 idNewStrictness :: Id -> StrictSig
359
360 idNewStrictness_maybe id = newStrictnessInfo (idInfo id)
361 idNewStrictness       id = idNewStrictness_maybe id `orElse` topSig
362
363 setIdNewStrictness :: Id -> StrictSig -> Id
364 setIdNewStrictness id sig = modifyIdInfo (`setNewStrictnessInfo` Just sig) id
365
366 zapIdNewStrictness :: Id -> Id
367 zapIdNewStrictness id = modifyIdInfo (`setNewStrictnessInfo` Nothing) id
368
369         ---------------------------------
370         -- WORKER ID
371 idWorkerInfo :: Id -> WorkerInfo
372 idWorkerInfo id = workerInfo (idInfo id)
373
374 setIdWorkerInfo :: Id -> WorkerInfo -> Id
375 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
376
377         ---------------------------------
378         -- UNFOLDING
379 idUnfolding :: Id -> Unfolding
380 idUnfolding id = unfoldingInfo (idInfo id)
381
382 setIdUnfolding :: Id -> Unfolding -> Id
383 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
384
385 #ifdef OLD_STRICTNESS
386         ---------------------------------
387         -- (OLD) DEMAND
388 idDemandInfo :: Id -> Demand.Demand
389 idDemandInfo id = demandInfo (idInfo id)
390
391 setIdDemandInfo :: Id -> Demand.Demand -> Id
392 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
393 #endif
394
395 idNewDemandInfo_maybe :: Id -> Maybe NewDemand.Demand
396 idNewDemandInfo       :: Id -> NewDemand.Demand
397
398 idNewDemandInfo_maybe id = newDemandInfo (idInfo id)
399 idNewDemandInfo       id = newDemandInfo (idInfo id) `orElse` NewDemand.topDmd
400
401 setIdNewDemandInfo :: Id -> NewDemand.Demand -> Id
402 setIdNewDemandInfo id dmd = modifyIdInfo (`setNewDemandInfo` Just dmd) id
403
404         ---------------------------------
405         -- SPECIALISATION
406 idSpecialisation :: Id -> SpecInfo
407 idSpecialisation id = specInfo (idInfo id)
408
409 idCoreRules :: Id -> [CoreRule]
410 idCoreRules id = specInfoRules (idSpecialisation id)
411
412 setIdSpecialisation :: Id -> SpecInfo -> Id
413 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
414
415         ---------------------------------
416         -- CAF INFO
417 idCafInfo :: Id -> CafInfo
418 #ifdef OLD_STRICTNESS
419 idCafInfo id = case cgInfo (idInfo id) of
420                   NoCgInfo -> pprPanic "idCafInfo" (ppr id)
421                   info     -> cgCafInfo info
422 #else
423 idCafInfo id = cafInfo (idInfo id)
424 #endif
425
426 setIdCafInfo :: Id -> CafInfo -> Id
427 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
428
429         ---------------------------------
430         -- CPR INFO
431 #ifdef OLD_STRICTNESS
432 idCprInfo :: Id -> CprInfo
433 idCprInfo id = cprInfo (idInfo id)
434
435 setIdCprInfo :: Id -> CprInfo -> Id
436 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
437 #endif
438
439         ---------------------------------
440         -- Occcurrence INFO
441 idOccInfo :: Id -> OccInfo
442 idOccInfo id = occInfo (idInfo id)
443
444 setIdOccInfo :: Id -> OccInfo -> Id
445 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
446 \end{code}
447
448
449         ---------------------------------
450         -- INLINING
451 The inline pragma tells us to be very keen to inline this Id, but it's still
452 OK not to if optimisation is switched off.
453
454 \begin{code}
455 idInlinePragma :: Id -> InlinePragInfo
456 idInlinePragma id = inlinePragInfo (idInfo id)
457
458 setInlinePragma :: Id -> InlinePragInfo -> Id
459 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
460
461 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
462 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
463 \end{code}
464
465
466         ---------------------------------
467         -- ONE-SHOT LAMBDAS
468 \begin{code}
469 idLBVarInfo :: Id -> LBVarInfo
470 idLBVarInfo id = lbvarInfo (idInfo id)
471
472 isOneShotBndr :: Id -> Bool
473 -- This one is the "business end", called externally.
474 -- Its main purpose is to encapsulate the Horrible State Hack
475 isOneShotBndr id = isOneShotLambda id || (isStateHackType (idType id))
476
477 isStateHackType :: Type -> Bool
478 isStateHackType ty
479   | opt_NoStateHack 
480   = False
481   | otherwise
482   = case splitTyConApp_maybe ty of
483         Just (tycon,_) -> tycon == statePrimTyCon
484         other          -> False
485         -- This is a gross hack.  It claims that 
486         -- every function over realWorldStatePrimTy is a one-shot
487         -- function.  This is pretty true in practice, and makes a big
488         -- difference.  For example, consider
489         --      a `thenST` \ r -> ...E...
490         -- The early full laziness pass, if it doesn't know that r is one-shot
491         -- will pull out E (let's say it doesn't mention r) to give
492         --      let lvl = E in a `thenST` \ r -> ...lvl...
493         -- When `thenST` gets inlined, we end up with
494         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
495         -- and we don't re-inline E.
496         --
497         -- It would be better to spot that r was one-shot to start with, but
498         -- I don't want to rely on that.
499         --
500         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
501         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
502
503
504 -- The OneShotLambda functions simply fiddle with the IdInfo flag
505 isOneShotLambda :: Id -> Bool
506 isOneShotLambda id = case idLBVarInfo id of
507                        IsOneShotLambda  -> True
508                        NoLBVarInfo      -> False
509
510 setOneShotLambda :: Id -> Id
511 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
512
513 clearOneShotLambda :: Id -> Id
514 clearOneShotLambda id 
515   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
516   | otherwise          = id                     
517
518 -- But watch out: this may change the type of something else
519 --      f = \x -> e
520 -- If we change the one-shot-ness of x, f's type changes
521 \end{code}
522
523 \begin{code}
524 zapLamIdInfo :: Id -> Id
525 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
526
527 zapDemandIdInfo id = maybeModifyIdInfo zapDemandInfo id
528 \end{code}
529