[project @ 2000-12-19 08:34:40 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 -- The Int gives the starting point for unique allocation
164 mkTemplateLocalsNum n tys = zipWith (mkSysLocal SLIT("tpl"))
165                                (getNumBuiltinUniques n (length tys))
166                                tys
167
168 mkTemplateLocal :: Int -> Type -> Id
169 mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
170 \end{code}
171
172
173 %************************************************************************
174 %*                                                                      *
175 \subsection[Id-general-funs]{General @Id@-related functions}
176 %*                                                                      *
177 %************************************************************************
178
179 \begin{code}
180 setIdType :: Id -> Type -> Id
181         -- Add free tyvar info to the type
182 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
183
184 idPrimRep :: Id -> PrimRep
185 idPrimRep id = typePrimRep (idType id)
186 \end{code}
187
188
189 %************************************************************************
190 %*                                                                      *
191 \subsection{Special Ids}
192 %*                                                                      *
193 %************************************************************************
194
195 \begin{code}
196 idFlavour :: Id -> IdFlavour
197 idFlavour id = flavourInfo (idInfo id)
198
199 setIdNoDiscard :: Id -> Id
200 setIdNoDiscard id       -- Make an Id into a NoDiscardId, unless it is already
201   = modifyIdInfo setNoDiscardInfo id
202
203 recordSelectorFieldLabel :: Id -> FieldLabel
204 recordSelectorFieldLabel id = case idFlavour id of
205                                 RecordSelId lbl -> lbl
206
207 isRecordSelector id = case idFlavour id of
208                         RecordSelId lbl -> True
209                         other           -> False
210
211 isPrimOpId id = case idFlavour id of
212                     PrimOpId op -> True
213                     other       -> False
214
215 isPrimOpId_maybe id = case idFlavour id of
216                             PrimOpId op -> Just op
217                             other       -> Nothing
218
219 isDataConId id = case idFlavour id of
220                         DataConId _ -> True
221                         other       -> False
222
223 isDataConId_maybe id = case idFlavour id of
224                           DataConId con -> Just con
225                           other         -> Nothing
226
227 isDataConWrapId_maybe id = case idFlavour id of
228                                   DataConWrapId con -> Just con
229                                   other             -> Nothing
230
231 isDataConWrapId id = case idFlavour id of
232                         DataConWrapId con -> True
233                         other             -> False
234
235 isSpecPragmaId id = case idFlavour id of
236                         SpecPragmaId -> True
237                         other        -> False
238
239 hasNoBinding id = case idFlavour id of
240                         DataConId _ -> True
241                         PrimOpId _  -> True
242                         other       -> False
243         -- hasNoBinding returns True of an Id which may not have a
244         -- binding, even though it is defined in this module.  Notably,
245         -- the constructors of a dictionary are in this situation.
246
247 isDictFunId id = case idFlavour id of
248                    DictFunId -> True
249                    other     -> False
250
251 -- Don't drop a binding for an exported Id,
252 -- if it otherwise looks dead.  
253 -- Perhaps a better name would be isDiscardableId
254 isExportedId :: Id -> Bool
255 isExportedId id = case idFlavour id of
256                         VanillaId  -> False
257                         other      -> True
258
259 isLocalId :: Id -> Bool
260 -- True of Ids that are locally defined, but are not constants
261 -- like data constructors, record selectors, and the like. 
262 -- See comments with CoreFVs.isLocalVar
263 isLocalId id 
264 #ifdef DEBUG
265   | not (isId id) = pprTrace "isLocalid" (ppr id) False
266   | otherwise
267 #endif
268   = case idFlavour id of
269          VanillaId    -> True
270          ExportedId   -> True
271          SpecPragmaId -> True
272          other        -> False
273 \end{code}
274
275
276 isImplicitId tells whether an Id's info is implied by other
277 declarations, so we don't need to put its signature in an interface
278 file, even if it's mentioned in some other interface unfolding.
279
280 \begin{code}
281 isImplicitId :: Id -> Bool
282 isImplicitId id
283   = case idFlavour id of
284         RecordSelId _   -> True -- Includes dictionary selectors
285         PrimOpId _      -> True
286         DataConId _     -> True
287         DataConWrapId _ -> True
288                 -- These are are implied by their type or class decl;
289                 -- remember that all type and class decls appear in the interface file.
290                 -- The dfun id must *not* be omitted, because it carries version info for
291                 -- the instance decl
292         other           -> False
293 \end{code}
294
295 \begin{code}
296 isDeadBinder :: Id -> Bool
297 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
298                   | otherwise = False   -- TyVars count as not dead
299
300 isIP id = isIPOcc (getOccName id)
301 \end{code}
302
303
304 %************************************************************************
305 %*                                                                      *
306 \subsection{IdInfo stuff}
307 %*                                                                      *
308 %************************************************************************
309
310 \begin{code}
311         ---------------------------------
312         -- ARITY
313 idArityInfo :: Id -> ArityInfo
314 idArityInfo id = arityInfo (idInfo id)
315
316 idArity :: Id -> Arity
317 idArity id = arityLowerBound (idArityInfo id)
318
319 setIdArityInfo :: Id -> ArityInfo -> Id
320 setIdArityInfo id arity = modifyIdInfo (`setArityInfo` arity) id
321
322         ---------------------------------
323         -- STRICTNESS
324 idStrictness :: Id -> StrictnessInfo
325 idStrictness id = strictnessInfo (idInfo id)
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 = isBottomingStrictness (idStrictness id)
333
334         ---------------------------------
335         -- TYPE GENERALISATION
336 idTyGenInfo :: Id -> TyGenInfo
337 idTyGenInfo id = tyGenInfo (idInfo id)
338
339 setIdTyGenInfo :: Id -> TyGenInfo -> Id
340 setIdTyGenInfo id tygen_info = modifyIdInfo (`setTyGenInfo` tygen_info) id
341
342         ---------------------------------
343         -- WORKER ID
344 idWorkerInfo :: Id -> WorkerInfo
345 idWorkerInfo id = workerInfo (idInfo id)
346
347 setIdWorkerInfo :: Id -> WorkerInfo -> Id
348 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
349
350         ---------------------------------
351         -- UNFOLDING
352 idUnfolding :: Id -> Unfolding
353 idUnfolding id = unfoldingInfo (idInfo id)
354
355 setIdUnfolding :: Id -> Unfolding -> Id
356 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
357
358         ---------------------------------
359         -- DEMAND
360 idDemandInfo :: Id -> Demand
361 idDemandInfo id = demandInfo (idInfo id)
362
363 setIdDemandInfo :: Id -> Demand -> Id
364 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
365
366         ---------------------------------
367         -- SPECIALISATION
368 idSpecialisation :: Id -> CoreRules
369 idSpecialisation id = specInfo (idInfo id)
370
371 setIdSpecialisation :: Id -> CoreRules -> Id
372 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
373
374         ---------------------------------
375         -- CAF INFO
376 idCafInfo :: Id -> CafInfo
377 idCafInfo id = cafInfo (idInfo id)
378
379 setIdCafInfo :: Id -> CafInfo -> Id
380 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
381
382         ---------------------------------
383         -- CPR INFO
384 idCprInfo :: Id -> CprInfo
385 idCprInfo id = cprInfo (idInfo id)
386
387 setIdCprInfo :: Id -> CprInfo -> Id
388 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
389
390         ---------------------------------
391         -- Occcurrence INFO
392 idOccInfo :: Id -> OccInfo
393 idOccInfo id = occInfo (idInfo id)
394
395 setIdOccInfo :: Id -> OccInfo -> Id
396 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
397 \end{code}
398
399
400         ---------------------------------
401         -- INLINING
402 The inline pragma tells us to be very keen to inline this Id, but it's still
403 OK not to if optimisation is switched off.
404
405 \begin{code}
406 idInlinePragma :: Id -> InlinePragInfo
407 idInlinePragma id = inlinePragInfo (idInfo id)
408
409 setInlinePragma :: Id -> InlinePragInfo -> Id
410 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
411
412 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
413 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
414 \end{code}
415
416
417         ---------------------------------
418         -- ONE-SHOT LAMBDAS
419 \begin{code}
420 idLBVarInfo :: Id -> LBVarInfo
421 idLBVarInfo id = lbvarInfo (idInfo id)
422
423 isOneShotLambda :: Id -> Bool
424 isOneShotLambda id = analysis || hack
425   where analysis = case idLBVarInfo id of
426                      LBVarInfo u    | u == usOnce             -> True
427                      other                                    -> False
428         hack     = case splitTyConApp_maybe (idType id) of
429                      Just (tycon,_) | tycon == statePrimTyCon -> True
430                      other                                    -> False
431
432         -- The last clause is a gross hack.  It claims that 
433         -- every function over realWorldStatePrimTy is a one-shot
434         -- function.  This is pretty true in practice, and makes a big
435         -- difference.  For example, consider
436         --      a `thenST` \ r -> ...E...
437         -- The early full laziness pass, if it doesn't know that r is one-shot
438         -- will pull out E (let's say it doesn't mention r) to give
439         --      let lvl = E in a `thenST` \ r -> ...lvl...
440         -- When `thenST` gets inlined, we end up with
441         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
442         -- and we don't re-inline E.
443         --
444         -- It would be better to spot that r was one-shot to start with, but
445         -- I don't want to rely on that.
446         --
447         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
448         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
449
450 setOneShotLambda :: Id -> Id
451 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` LBVarInfo usOnce) id
452
453 clearOneShotLambda :: Id -> Id
454 clearOneShotLambda id 
455   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
456   | otherwise          = id                     
457
458 -- But watch out: this may change the type of something else
459 --      f = \x -> e
460 -- If we change the one-shot-ness of x, f's type changes
461 \end{code}
462
463 \begin{code}
464 zapFragileIdInfo :: Id -> Id
465 zapFragileIdInfo id = maybeModifyIdInfo zapFragileInfo id
466
467 zapLamIdInfo :: Id -> Id
468 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
469 \end{code}
470