[project @ 2001-07-23 10:54:46 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, setIdNoDiscard, 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         setIdArityInfo,
47         setIdDemandInfo, setIdNewDemandInfo,
48         setIdStrictness, setIdNewStrictness,
49         setIdTyGenInfo,
50         setIdWorkerInfo,
51         setIdSpecialisation,
52         setIdCgInfo,
53         setIdCprInfo,
54         setIdOccInfo,
55
56         idArity, idArityInfo, 
57         idDemandInfo, idNewDemandInfo,
58         idStrictness, idNewStrictness, idNewStrictness_maybe, getNewStrictness,
59         idTyGenInfo,
60         idWorkerInfo,
61         idUnfolding,
62         idSpecialisation,
63         idCgInfo,
64         idCafInfo,
65         idCgArity,
66         idCprInfo,
67         idLBVarInfo,
68         idOccInfo,
69
70         newStrictnessFromOld    -- Temporary
71
72     ) where
73
74 #include "HsVersions.h"
75
76
77 import CoreSyn          ( Unfolding, CoreRules )
78 import BasicTypes       ( Arity )
79 import Var              ( Id, DictId,
80                           isId, isExportedId, isSpecPragmaId, isLocalId,
81                           idName, idType, idUnique, idInfo, isGlobalId,
82                           setIdName, setVarType, setIdUnique, setIdNoDiscard,
83                           setIdInfo, lazySetIdInfo, modifyIdInfo, 
84                           maybeModifyIdInfo,
85                           globalIdDetails, setGlobalIdDetails
86                         )
87 import qualified Var    ( mkLocalId, mkGlobalId, mkSpecPragmaId )
88 import Type             ( Type, typePrimRep, addFreeTyVars, 
89                           usOnce, eqUsage, seqType, splitTyConApp_maybe )
90
91 import IdInfo 
92
93 import qualified Demand ( Demand )
94 import NewDemand        ( Demand, DmdResult(..), StrictSig, topSig, isBotRes,
95                           isBottomingSig, splitStrictSig, strictSigResInfo
96                         )
97 import Name             ( Name, OccName,
98                           mkSysLocalName, mkLocalName,
99                           getOccName, getSrcLoc
100                         ) 
101 import OccName          ( UserFS, mkWorkerOcc )
102 import PrimRep          ( PrimRep )
103 import TysPrim          ( statePrimTyCon )
104 import FieldLabel       ( FieldLabel )
105 import Maybes           ( orElse )
106 import SrcLoc           ( SrcLoc )
107 import Outputable
108 import Unique           ( Unique, mkBuiltinUnique )
109
110 infixl  1 `setIdUnfolding`,
111           `setIdArityInfo`,
112           `setIdDemandInfo`,
113           `setIdStrictness`,
114           `setIdNewDemandInfo`,
115           `setIdNewStrictness`,
116           `setIdTyGenInfo`,
117           `setIdWorkerInfo`,
118           `setIdSpecialisation`,
119           `setInlinePragma`,
120           `idCafInfo`,
121           `idCprInfo`
122
123         -- infixl so you can say (id `set` a `set` b)
124 \end{code}
125
126
127
128 %************************************************************************
129 %*                                                                      *
130 \subsection{Simple Id construction}
131 %*                                                                      *
132 %************************************************************************
133
134 Absolutely all Ids are made by mkId.  It is just like Var.mkId,
135 but in addition it pins free-tyvar-info onto the Id's type, 
136 where it can easily be found.
137
138 \begin{code}
139 mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id
140 mkLocalIdWithInfo name ty info = Var.mkLocalId name (addFreeTyVars ty) info
141
142 mkSpecPragmaId :: OccName -> Unique -> Type -> SrcLoc -> Id
143 mkSpecPragmaId occ uniq ty loc = Var.mkSpecPragmaId (mkLocalName uniq occ loc)
144                                                     (addFreeTyVars ty)
145                                                     vanillaIdInfo
146
147 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
148 mkGlobalId details name ty info = Var.mkGlobalId details name (addFreeTyVars ty) info
149 \end{code}
150
151 \begin{code}
152 mkLocalId :: Name -> Type -> Id
153 mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo
154
155 -- SysLocal: for an Id being created by the compiler out of thin air...
156 -- UserLocal: an Id with a name the user might recognize...
157 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
158 mkSysLocal  :: UserFS  -> Unique -> Type -> Id
159 mkVanillaGlobal :: Name -> Type -> IdInfo -> Id
160
161 mkSysLocal  fs uniq ty      = mkLocalId (mkSysLocalName uniq fs)      ty
162 mkUserLocal occ uniq ty loc = mkLocalId (mkLocalName    uniq occ loc) ty
163 mkVanillaGlobal             = mkGlobalId VanillaGlobal
164 \end{code}
165
166 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
167 @Uniques@, but that's OK because the templates are supposed to be
168 instantiated before use.
169  
170 \begin{code}
171 -- "Wild Id" typically used when you need a binder that you don't expect to use
172 mkWildId :: Type -> Id
173 mkWildId ty = mkSysLocal SLIT("wild") (mkBuiltinUnique 1) ty
174
175 mkWorkerId :: Unique -> Id -> Type -> Id
176 -- A worker gets a local name.  CoreTidy will globalise it if necessary.
177 mkWorkerId uniq unwrkr ty
178   = mkLocalId wkr_name ty
179   where
180     wkr_name = mkLocalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcLoc unwrkr)
181
182 -- "Template locals" typically used in unfoldings
183 mkTemplateLocals :: [Type] -> [Id]
184 mkTemplateLocals tys = zipWith mkTemplateLocal [1..] tys
185
186 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
187 -- The Int gives the starting point for unique allocation
188 mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys
189
190 mkTemplateLocal :: Int -> Type -> Id
191 mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
192 \end{code}
193
194
195 %************************************************************************
196 %*                                                                      *
197 \subsection[Id-general-funs]{General @Id@-related functions}
198 %*                                                                      *
199 %************************************************************************
200
201 \begin{code}
202 setIdType :: Id -> Type -> Id
203         -- Add free tyvar info to the type
204 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
205
206 idPrimRep :: Id -> PrimRep
207 idPrimRep id = typePrimRep (idType id)
208 \end{code}
209
210
211 %************************************************************************
212 %*                                                                      *
213 \subsection{Special Ids}
214 %*                                                                      *
215 %************************************************************************
216
217 The @SpecPragmaId@ exists only to make Ids that are
218 on the *LHS* of bindings created by SPECIALISE pragmas; 
219 eg:             s = f Int d
220 The SpecPragmaId is never itself mentioned; it
221 exists solely so that the specialiser will find
222 the call to f, and make specialised version of it.
223 The SpecPragmaId binding is discarded by the specialiser
224 when it gathers up overloaded calls.
225 Meanwhile, it is not discarded as dead code.
226
227
228 \begin{code}
229 recordSelectorFieldLabel :: Id -> FieldLabel
230 recordSelectorFieldLabel id = case globalIdDetails id of
231                                  RecordSelId lbl -> lbl
232
233 isRecordSelector id = case globalIdDetails id of
234                         RecordSelId lbl -> True
235                         other           -> False
236
237 isPrimOpId id = case globalIdDetails id of
238                     PrimOpId op -> True
239                     other       -> False
240
241 isPrimOpId_maybe id = case globalIdDetails id of
242                             PrimOpId op -> Just op
243                             other       -> Nothing
244
245 isFCallId id = case globalIdDetails id of
246                     FCallId call -> True
247                     other        -> False
248
249 isFCallId_maybe id = case globalIdDetails id of
250                             FCallId call -> Just call
251                             other        -> Nothing
252
253 isDataConId id = case globalIdDetails id of
254                         DataConId _ -> True
255                         other       -> False
256
257 isDataConId_maybe id = case globalIdDetails id of
258                           DataConId con -> Just con
259                           other         -> Nothing
260
261 isDataConWrapId_maybe id = case globalIdDetails id of
262                                   DataConWrapId con -> Just con
263                                   other             -> Nothing
264
265 isDataConWrapId id = case globalIdDetails id of
266                         DataConWrapId con -> True
267                         other             -> False
268
269         -- hasNoBinding returns True of an Id which may not have a
270         -- binding, even though it is defined in this module.  Notably,
271         -- the constructors of a dictionary are in this situation.
272 hasNoBinding id = case globalIdDetails id of
273                         DataConId _ -> True
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 idArityInfo :: Id -> ArityInfo
313 idArityInfo id = arityInfo (idInfo id)
314
315 idArity :: Id -> Arity
316 idArity id = arityLowerBound (idArityInfo id)
317
318 setIdArityInfo :: Id -> Arity -> Id
319 setIdArityInfo id arity = modifyIdInfo (`setArityInfo` arity) id
320
321         ---------------------------------
322         -- STRICTNESS 
323 idStrictness :: Id -> StrictnessInfo
324 idStrictness id = case strictnessInfo (idInfo id) of
325                         NoStrictnessInfo -> case idNewStrictness_maybe id of
326                                                 Just sig -> oldStrictnessFromNew sig
327                                                 Nothing  -> NoStrictnessInfo
328                         strictness -> strictness
329
330 setIdStrictness :: Id -> StrictnessInfo -> Id
331 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
332
333 -- isBottomingId returns true if an application to n args would diverge
334 isBottomingId :: Id -> Bool
335 isBottomingId id = isBottomingSig (idNewStrictness id)
336
337 idNewStrictness_maybe :: Id -> Maybe StrictSig
338 idNewStrictness :: Id -> StrictSig
339
340 idNewStrictness_maybe id = newStrictnessInfo (idInfo id)
341 idNewStrictness       id = idNewStrictness_maybe id `orElse` topSig
342
343 getNewStrictness :: Id -> StrictSig
344 -- First tries the "new-strictness" field, and then
345 -- reverts to the old one. This is just until we have
346 -- cross-module info for new strictness
347 getNewStrictness id = idNewStrictness_maybe id `orElse` newStrictnessFromOld id
348                       
349 newStrictnessFromOld :: Id -> StrictSig
350 newStrictnessFromOld id = mkNewStrictnessInfo id (idArity id) (idStrictness id) (idCprInfo id)
351
352 oldStrictnessFromNew :: StrictSig -> StrictnessInfo
353 oldStrictnessFromNew sig = mkStrictnessInfo (map oldDemand dmds, isBotRes res_info)
354                          where
355                            (dmds, res_info) = splitStrictSig sig
356
357 setIdNewStrictness :: Id -> StrictSig -> Id
358 setIdNewStrictness id sig = modifyIdInfo (`setNewStrictnessInfo` Just sig) 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 idCafInfo id = cgCafInfo (idCgInfo id)
424
425         ---------------------------------
426         -- CG ARITY
427 idCgArity :: Id -> Arity
428 idCgArity id = cgArity (idCgInfo id)
429
430         ---------------------------------
431         -- CPR INFO
432 idCprInfo :: Id -> CprInfo
433 idCprInfo id = case cprInfo (idInfo id) of
434                  NoCPRInfo -> case strictSigResInfo (idNewStrictness id) of
435                                 RetCPR -> ReturnsCPR
436                                 other  -> NoCPRInfo
437                  ReturnsCPR -> ReturnsCPR
438
439 setIdCprInfo :: Id -> CprInfo -> Id
440 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
441
442         ---------------------------------
443         -- Occcurrence INFO
444 idOccInfo :: Id -> OccInfo
445 idOccInfo id = occInfo (idInfo id)
446
447 setIdOccInfo :: Id -> OccInfo -> Id
448 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
449 \end{code}
450
451
452         ---------------------------------
453         -- INLINING
454 The inline pragma tells us to be very keen to inline this Id, but it's still
455 OK not to if optimisation is switched off.
456
457 \begin{code}
458 idInlinePragma :: Id -> InlinePragInfo
459 idInlinePragma id = inlinePragInfo (idInfo id)
460
461 setInlinePragma :: Id -> InlinePragInfo -> Id
462 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
463
464 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
465 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
466 \end{code}
467
468
469         ---------------------------------
470         -- ONE-SHOT LAMBDAS
471 \begin{code}
472 idLBVarInfo :: Id -> LBVarInfo
473 idLBVarInfo id = lbvarInfo (idInfo id)
474
475 isOneShotLambda :: Id -> Bool
476 isOneShotLambda id = analysis || hack
477   where analysis = case idLBVarInfo id of
478                      LBVarInfo u    | u `eqUsage` usOnce      -> True
479                      other                                    -> False
480         hack     = case splitTyConApp_maybe (idType id) of
481                      Just (tycon,_) | tycon == statePrimTyCon -> True
482                      other                                    -> False
483
484         -- The last clause is a gross hack.  It claims that 
485         -- every function over realWorldStatePrimTy is a one-shot
486         -- function.  This is pretty true in practice, and makes a big
487         -- difference.  For example, consider
488         --      a `thenST` \ r -> ...E...
489         -- The early full laziness pass, if it doesn't know that r is one-shot
490         -- will pull out E (let's say it doesn't mention r) to give
491         --      let lvl = E in a `thenST` \ r -> ...lvl...
492         -- When `thenST` gets inlined, we end up with
493         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
494         -- and we don't re-inline E.
495         --
496         -- It would be better to spot that r was one-shot to start with, but
497         -- I don't want to rely on that.
498         --
499         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
500         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
501
502 setOneShotLambda :: Id -> Id
503 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` LBVarInfo usOnce) id
504
505 clearOneShotLambda :: Id -> Id
506 clearOneShotLambda id 
507   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
508   | otherwise          = id                     
509
510 -- But watch out: this may change the type of something else
511 --      f = \x -> e
512 -- If we change the one-shot-ness of x, f's type changes
513 \end{code}
514
515 \begin{code}
516 zapLamIdInfo :: Id -> Id
517 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
518
519 zapDemandIdInfo id = maybeModifyIdInfo zapDemandInfo id
520 \end{code}