[project @ 2000-10-31 17:30:16 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         omitIfaceSigForId, isDeadBinder,
26         exportWithOrigOccName,
27         externallyVisibleId,
28         idFreeTyVars,
29         isIP,
30         isSpecPragmaId, isRecordSelector,
31         isPrimOpId, isPrimOpId_maybe, 
32         isDataConId, isDataConId_maybe, isDataConWrapId, 
33                 isDataConWrapId_maybe,
34         isBottomingId,
35         isExportedId, isUserExportedId,
36         hasNoBinding,
37
38         -- Inline pragma stuff
39         idInlinePragma, setInlinePragma, modifyInlinePragma, 
40
41
42         -- One shot lambda stuff
43         isOneShotLambda, setOneShotLambda, clearOneShotLambda,
44
45         -- IdInfo stuff
46         setIdUnfolding,
47         setIdArityInfo,
48         setIdDemandInfo,
49         setIdStrictness,
50         setIdWorkerInfo,
51         setIdSpecialisation,
52         setIdCafInfo,
53         setIdCprInfo,
54         setIdOccInfo,
55
56         idArity, idArityInfo, 
57         idFlavour,
58         idDemandInfo,
59         idStrictness,
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 VarSet
84 import Type             ( Type, tyVarsOfType, typePrimRep, addFreeTyVars, 
85                           seqType, splitTyConApp_maybe )
86
87 import IdInfo 
88
89 import Demand           ( Demand )
90 import Name             ( Name, OccName,
91                           mkSysLocalName, mkLocalName,
92                           isUserExportedName, getOccName, isIPOcc
93                         ) 
94 import OccName          ( UserFS )
95 import PrimRep          ( PrimRep )
96 import TysPrim          ( statePrimTyCon )
97 import FieldLabel       ( FieldLabel )
98 import SrcLoc           ( SrcLoc )
99 import Unique           ( Unique, mkBuiltinUnique, getBuiltinUniques, 
100                           getNumBuiltinUniques )
101
102 infixl  1 `setIdUnfolding`,
103           `setIdArityInfo`,
104           `setIdDemandInfo`,
105           `setIdStrictness`,
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                   where
132                     info' | isUserExportedName name = setNoDiscardInfo info
133                           | otherwise               = info
134 \end{code}
135
136 \begin{code}
137 mkVanillaId :: Name -> Type -> Id
138 mkVanillaId name ty = mkId name ty vanillaIdInfo
139
140 -- SysLocal: for an Id being created by the compiler out of thin air...
141 -- UserLocal: an Id with a name the user might recognize...
142 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
143 mkSysLocal  :: UserFS  -> Unique -> Type -> Id
144
145 mkSysLocal  fs uniq ty      = mkVanillaId (mkSysLocalName uniq fs)      ty
146 mkUserLocal occ uniq ty loc = mkVanillaId (mkLocalName    uniq occ loc) ty
147 \end{code}
148
149 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
150 @Uniques@, but that's OK because the templates are supposed to be
151 instantiated before use.
152
153 \begin{code}
154 -- "Wild Id" typically used when you need a binder that you don't expect to use
155 mkWildId :: Type -> Id
156 mkWildId ty = mkSysLocal SLIT("wild") (mkBuiltinUnique 1) ty
157
158 -- "Template locals" typically used in unfoldings
159 mkTemplateLocals :: [Type] -> [Id]
160 mkTemplateLocals tys = zipWith (mkSysLocal SLIT("tpl"))
161                                (getBuiltinUniques (length tys))
162                                tys
163
164 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
165 mkTemplateLocalsNum n tys = zipWith (mkSysLocal SLIT("tpl"))
166                                (getNumBuiltinUniques n (length tys))
167                                tys
168
169 mkTemplateLocal :: Int -> Type -> Id
170 mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
171 \end{code}
172
173
174 %************************************************************************
175 %*                                                                      *
176 \subsection[Id-general-funs]{General @Id@-related functions}
177 %*                                                                      *
178 %************************************************************************
179
180 \begin{code}
181 idFreeTyVars :: Id -> TyVarSet
182 idFreeTyVars id = tyVarsOfType (idType id)
183
184 setIdType :: Id -> Type -> Id
185         -- Add free tyvar info to the type
186 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
187
188 idPrimRep :: Id -> PrimRep
189 idPrimRep id = typePrimRep (idType id)
190 \end{code}
191
192
193 %************************************************************************
194 %*                                                                      *
195 \subsection{Special Ids}
196 %*                                                                      *
197 %************************************************************************
198
199 \begin{code}
200 idFlavour :: Id -> IdFlavour
201 idFlavour id = flavourInfo (idInfo id)
202
203 setIdNoDiscard :: Id -> Id
204 setIdNoDiscard id       -- Make an Id into a NoDiscardId, unless it is already
205   = modifyIdInfo setNoDiscardInfo id
206
207 recordSelectorFieldLabel :: Id -> FieldLabel
208 recordSelectorFieldLabel id = case idFlavour id of
209                                 RecordSelId lbl -> lbl
210
211 isRecordSelector id = case idFlavour id of
212                         RecordSelId lbl -> True
213                         other           -> False
214
215 isPrimOpId id = case idFlavour id of
216                     PrimOpId op -> True
217                     other       -> False
218
219 isPrimOpId_maybe id = case idFlavour id of
220                             PrimOpId op -> Just op
221                             other       -> Nothing
222
223 isDataConId id = case idFlavour id of
224                         DataConId _ -> True
225                         other       -> False
226
227 isDataConId_maybe id = case idFlavour id of
228                           DataConId con -> Just con
229                           other         -> Nothing
230
231 isDataConWrapId_maybe id = case idFlavour id of
232                                   DataConWrapId con -> Just con
233                                   other             -> Nothing
234
235 isDataConWrapId id = case idFlavour id of
236                         DataConWrapId con -> True
237                         other             -> False
238
239 isSpecPragmaId id = case idFlavour id of
240                         SpecPragmaId -> True
241                         other        -> False
242
243 hasNoBinding id = case idFlavour id of
244                         DataConId _ -> True
245                         PrimOpId _  -> True
246                         other       -> False
247         -- hasNoBinding returns True of an Id which may not have a
248         -- binding, even though it is defined in this module.  Notably,
249         -- the constructors of a dictionary are in this situation.
250
251 -- Don't drop a binding for an exported Id,
252 -- if it otherwise looks dead.  
253 isExportedId :: Id -> Bool
254 isExportedId id = isUserExportedId id   -- Try this
255 {-
256   case idFlavour id of
257                         VanillaId -> False
258                         other     -> True       -- All the others are no-discard
259 -}
260
261 -- Say if an Id was exported by the user
262 -- Implies isExportedId (see mkId above)
263 isUserExportedId :: Id -> Bool
264 isUserExportedId id = isUserExportedName (idName id)
265 \end{code}
266
267
268 omitIfaceSigForId tells whether an Id's info is implied by other declarations,
269 so we don't need to put its signature in an interface file, even if it's mentioned
270 in some other interface unfolding.
271
272 \begin{code}
273 omitIfaceSigForId :: Id -> Bool
274 omitIfaceSigForId id
275   | otherwise
276   = case idFlavour id of
277         RecordSelId _   -> True -- Includes dictionary selectors
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
286         other          -> False -- Don't omit!
287
288 -- Certain names must be exported with their original occ names, because
289 -- these names are bound by either a class declaration or a data declaration
290 -- or an explicit user export.
291 exportWithOrigOccName :: Id -> Bool
292 exportWithOrigOccName id = omitIfaceSigForId id || isUserExportedId id
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         -- WORKER ID
336 idWorkerInfo :: Id -> WorkerInfo
337 idWorkerInfo id = workerInfo (idInfo id)
338
339 setIdWorkerInfo :: Id -> WorkerInfo -> Id
340 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
341
342         ---------------------------------
343         -- UNFOLDING
344 idUnfolding :: Id -> Unfolding
345 idUnfolding id = unfoldingInfo (idInfo id)
346
347 setIdUnfolding :: Id -> Unfolding -> Id
348 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
349
350         ---------------------------------
351         -- DEMAND
352 idDemandInfo :: Id -> Demand
353 idDemandInfo id = demandInfo (idInfo id)
354
355 setIdDemandInfo :: Id -> Demand -> Id
356 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
357
358         ---------------------------------
359         -- SPECIALISATION
360 idSpecialisation :: Id -> CoreRules
361 idSpecialisation id = specInfo (idInfo id)
362
363 setIdSpecialisation :: Id -> CoreRules -> Id
364 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
365
366         ---------------------------------
367         -- CAF INFO
368 idCafInfo :: Id -> CafInfo
369 idCafInfo id = cafInfo (idInfo id)
370
371 setIdCafInfo :: Id -> CafInfo -> Id
372 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
373
374         ---------------------------------
375         -- CPR INFO
376 idCprInfo :: Id -> CprInfo
377 idCprInfo id = cprInfo (idInfo id)
378
379 setIdCprInfo :: Id -> CprInfo -> Id
380 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
381
382         ---------------------------------
383         -- Occcurrence INFO
384 idOccInfo :: Id -> OccInfo
385 idOccInfo id = occInfo (idInfo id)
386
387 setIdOccInfo :: Id -> OccInfo -> Id
388 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
389 \end{code}
390
391
392         ---------------------------------
393         -- INLINING
394 The inline pragma tells us to be very keen to inline this Id, but it's still
395 OK not to if optimisation is switched off.
396
397 \begin{code}
398 idInlinePragma :: Id -> InlinePragInfo
399 idInlinePragma id = inlinePragInfo (idInfo id)
400
401 setInlinePragma :: Id -> InlinePragInfo -> Id
402 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
403
404 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
405 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
406 \end{code}
407
408
409         ---------------------------------
410         -- ONE-SHOT LAMBDAS
411 \begin{code}
412 idLBVarInfo :: Id -> LBVarInfo
413 idLBVarInfo id = lbvarInfo (idInfo id)
414
415 isOneShotLambda :: Id -> Bool
416 isOneShotLambda id = case idLBVarInfo id of
417                         IsOneShotLambda -> True
418                         NoLBVarInfo     -> case splitTyConApp_maybe (idType id) of
419                                                 Just (tycon,_) -> tycon == statePrimTyCon
420                                                 other          -> False
421         -- The last clause is a gross hack.  It claims that 
422         -- every function over realWorldStatePrimTy is a one-shot
423         -- function.  This is pretty true in practice, and makes a big
424         -- difference.  For example, consider
425         --      a `thenST` \ r -> ...E...
426         -- The early full laziness pass, if it doesn't know that r is one-shot
427         -- will pull out E (let's say it doesn't mention r) to give
428         --      let lvl = E in a `thenST` \ r -> ...lvl...
429         -- When `thenST` gets inlined, we end up with
430         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
431         -- and we don't re-inline E.
432         --
433         -- It would be better to spot that r was one-shot to start with, but
434         -- I don't want to rely on that.
435         --
436         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
437         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
438
439 setOneShotLambda :: Id -> Id
440 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
441
442 clearOneShotLambda :: Id -> Id
443 clearOneShotLambda id 
444   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
445   | otherwise          = id                     
446
447 -- But watch out: this may change the type of something else
448 --      f = \x -> e
449 -- If we change the one-shot-ness of x, f's type changes
450 \end{code}
451
452 \begin{code}
453 zapFragileIdInfo :: Id -> Id
454 zapFragileIdInfo id = maybeModifyIdInfo zapFragileInfo id
455
456 zapLamIdInfo :: Id -> Id
457 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
458 \end{code}
459
460
461
462
463
464
465
466
467
468
469