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