[project @ 2001-03-01 17:10:06 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         zapLamIdInfo, zapDemandIdInfo,
23
24         -- Predicates
25         isImplicitId, isDeadBinder,
26         externallyVisibleId,
27         isSpecPragmaId, isRecordSelector,
28         isPrimOpId, isPrimOpId_maybe, isDictFunId,
29         isDataConId, isDataConId_maybe, 
30         isDataConWrapId, isDataConWrapId_maybe,
31         isBottomingId,
32         isExportedId, isLocalId, 
33         hasNoBinding,
34
35         -- Inline pragma stuff
36         idInlinePragma, setInlinePragma, modifyInlinePragma, 
37
38
39         -- One shot lambda stuff
40         isOneShotLambda, setOneShotLambda, clearOneShotLambda,
41
42         -- IdInfo stuff
43         setIdUnfolding,
44         setIdArityInfo,
45         setIdDemandInfo,
46         setIdStrictness,
47         setIdTyGenInfo,
48         setIdWorkerInfo,
49         setIdSpecialisation,
50         setIdCafInfo,
51         setIdCprInfo,
52         setIdOccInfo,
53
54         idArity, idArityInfo, 
55         idFlavour,
56         idDemandInfo,
57         idStrictness,
58         idTyGenInfo,
59         idWorkerInfo,
60         idUnfolding,
61         idSpecialisation,
62         idCafInfo,
63         idCprInfo,
64         idLBVarInfo,
65         idOccInfo,
66
67     ) where
68
69 #include "HsVersions.h"
70
71
72 import CoreSyn          ( Unfolding, CoreRules )
73 import BasicTypes       ( Arity )
74 import Var              ( Id, DictId,
75                           isId, mkIdVar,
76                           idName, idType, idUnique, idInfo,
77                           setIdName, setVarType, setIdUnique, 
78                           setIdInfo, lazySetIdInfo, modifyIdInfo, 
79                           maybeModifyIdInfo,
80                           externallyVisibleId
81                         )
82 import Type             ( Type, typePrimRep, addFreeTyVars, 
83                           usOnce, seqType, splitTyConApp_maybe )
84
85 import IdInfo 
86
87 import Demand           ( Demand )
88 import Name             ( Name, OccName,
89                           mkSysLocalName, mkLocalName,
90                           getOccName
91                         ) 
92 import OccName          ( UserFS )
93 import PrimRep          ( PrimRep )
94 import TysPrim          ( statePrimTyCon )
95 import FieldLabel       ( FieldLabel )
96 import SrcLoc           ( SrcLoc )
97 import Unique           ( Unique, mkBuiltinUnique, getBuiltinUniques, 
98                           getNumBuiltinUniques )
99 import Outputable
100
101 infixl  1 `setIdUnfolding`,
102           `setIdArityInfo`,
103           `setIdDemandInfo`,
104           `setIdStrictness`,
105           `setIdTyGenInfo`,
106           `setIdWorkerInfo`,
107           `setIdSpecialisation`,
108           `setInlinePragma`,
109           `idCafInfo`,
110           `idCprInfo`
111
112         -- infixl so you can say (id `set` a `set` b)
113 \end{code}
114
115
116
117 %************************************************************************
118 %*                                                                      *
119 \subsection{Simple Id construction}
120 %*                                                                      *
121 %************************************************************************
122
123 Absolutely all Ids are made by mkId.  It 
124         a) Pins free-tyvar-info onto the Id's type, 
125            where it can easily be found.
126         b) Ensures that exported Ids are 
127
128 \begin{code}
129 mkId :: Name -> Type -> IdInfo -> Id
130 mkId name ty info = mkIdVar name (addFreeTyVars ty) info
131 \end{code}
132
133 \begin{code}
134 mkVanillaId :: Name -> Type -> Id
135 mkVanillaId name ty = mkId name ty vanillaIdInfo
136
137 -- SysLocal: for an Id being created by the compiler out of thin air...
138 -- UserLocal: an Id with a name the user might recognize...
139 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
140 mkSysLocal  :: UserFS  -> Unique -> Type -> Id
141
142 mkSysLocal  fs uniq ty      = mkVanillaId (mkSysLocalName uniq fs)      ty
143 mkUserLocal occ uniq ty loc = mkVanillaId (mkLocalName    uniq occ loc) ty
144 \end{code}
145
146 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
147 @Uniques@, but that's OK because the templates are supposed to be
148 instantiated before use.
149
150 \begin{code}
151 -- "Wild Id" typically used when you need a binder that you don't expect to use
152 mkWildId :: Type -> Id
153 mkWildId ty = mkSysLocal SLIT("wild") (mkBuiltinUnique 1) ty
154
155 -- "Template locals" typically used in unfoldings
156 mkTemplateLocals :: [Type] -> [Id]
157 mkTemplateLocals tys = zipWith (mkSysLocal SLIT("tpl"))
158                                (getBuiltinUniques (length tys))
159                                tys
160
161 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
162 -- The Int gives the starting point for unique allocation
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 \end{code}
299
300
301 %************************************************************************
302 %*                                                                      *
303 \subsection{IdInfo stuff}
304 %*                                                                      *
305 %************************************************************************
306
307 \begin{code}
308         ---------------------------------
309         -- ARITY
310 idArityInfo :: Id -> ArityInfo
311 idArityInfo id = arityInfo (idInfo id)
312
313 idArity :: Id -> Arity
314 idArity id = arityLowerBound (idArityInfo id)
315
316 setIdArityInfo :: Id -> ArityInfo -> Id
317 setIdArityInfo id arity = modifyIdInfo (`setArityInfo` arity) id
318
319         ---------------------------------
320         -- STRICTNESS
321 idStrictness :: Id -> StrictnessInfo
322 idStrictness id = strictnessInfo (idInfo id)
323
324 setIdStrictness :: Id -> StrictnessInfo -> Id
325 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
326
327 -- isBottomingId returns true if an application to n args would diverge
328 isBottomingId :: Id -> Bool
329 isBottomingId id = isBottomingStrictness (idStrictness id)
330
331         ---------------------------------
332         -- TYPE GENERALISATION
333 idTyGenInfo :: Id -> TyGenInfo
334 idTyGenInfo id = tyGenInfo (idInfo id)
335
336 setIdTyGenInfo :: Id -> TyGenInfo -> Id
337 setIdTyGenInfo id tygen_info = modifyIdInfo (`setTyGenInfo` tygen_info) id
338
339         ---------------------------------
340         -- WORKER ID
341 idWorkerInfo :: Id -> WorkerInfo
342 idWorkerInfo id = workerInfo (idInfo id)
343
344 setIdWorkerInfo :: Id -> WorkerInfo -> Id
345 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
346
347         ---------------------------------
348         -- UNFOLDING
349 idUnfolding :: Id -> Unfolding
350 idUnfolding id = unfoldingInfo (idInfo id)
351
352 setIdUnfolding :: Id -> Unfolding -> Id
353 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
354
355         ---------------------------------
356         -- DEMAND
357 idDemandInfo :: Id -> Demand
358 idDemandInfo id = demandInfo (idInfo id)
359
360 setIdDemandInfo :: Id -> Demand -> Id
361 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
362
363         ---------------------------------
364         -- SPECIALISATION
365 idSpecialisation :: Id -> CoreRules
366 idSpecialisation id = specInfo (idInfo id)
367
368 setIdSpecialisation :: Id -> CoreRules -> Id
369 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
370
371         ---------------------------------
372         -- CAF INFO
373 idCafInfo :: Id -> CafInfo
374 idCafInfo id = cafInfo (idInfo id)
375
376 setIdCafInfo :: Id -> CafInfo -> Id
377 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) 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}