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