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