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