[project @ 2000-05-25 12:41:14 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, 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
31         -- Inline pragma stuff
32         idInlinePragma, setInlinePragma, modifyInlinePragma, 
33
34         isSpecPragmaId, isRecordSelector,
35         isPrimOpId, isPrimOpId_maybe, 
36         isDataConId, isDataConId_maybe, isDataConWrapId, isDataConWrapId_maybe,
37         isBottomingId,
38         isExportedId, isUserExportedId,
39         mayHaveNoBinding,
40
41         -- One shot lambda stuff
42         isOneShotLambda, setOneShotLambda, clearOneShotLambda,
43
44         -- IdInfo stuff
45         setIdUnfolding,
46         setIdArityInfo,
47         setIdDemandInfo,
48         setIdStrictness,
49         setIdWorkerInfo,
50         setIdSpecialisation,
51         setIdUpdateInfo,
52         setIdCafInfo,
53         setIdCprInfo,
54         setIdOccInfo,
55
56         idArity, idArityInfo, 
57         idFlavour,
58         idDemandInfo,
59         idStrictness,
60         idWorkerInfo,
61         idUnfolding,
62         idSpecialisation,
63         idUpdateInfo,
64         idCafInfo,
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, mkIdVar,
78                           idName, idType, idUnique, idInfo,
79                           setIdName, setVarType, setIdUnique, 
80                           setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo,
81                           externallyVisibleId
82                         )
83 import VarSet
84 import Type             ( Type, tyVarsOfType, typePrimRep, addFreeTyVars, seqType, splitTyConApp_maybe )
85
86 import IdInfo 
87
88 import Demand           ( Demand, isStrict, wwLazy )
89 import Name             ( Name, OccName,
90                           mkSysLocalName, mkLocalName,
91                           isWiredInName, isUserExportedName,
92                           getOccName, isIPOcc
93                         ) 
94 import OccName          ( UserFS )
95 import PrimRep          ( PrimRep )
96 import PrimOp           ( PrimOp, primOpIsCheap )
97 import TysPrim          ( statePrimTyCon )
98 import FieldLabel       ( FieldLabel )
99 import SrcLoc           ( SrcLoc )
100 import Unique           ( Unique, mkBuiltinUnique, getBuiltinUniques )
101 import Outputable
102
103 infixl  1 `setIdUnfolding`,
104           `setIdArityInfo`,
105           `setIdDemandInfo`,
106           `setIdStrictness`,
107           `setIdWorkerInfo`,
108           `setIdSpecialisation`,
109           `setIdUpdateInfo`,
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 
126         a) Pins free-tyvar-info onto the Id's type, 
127            where it can easily be found.
128         b) Ensures that exported Ids are 
129
130 \begin{code}
131 mkId :: Name -> Type -> IdInfo -> Id
132 mkId name ty info = mkIdVar name (addFreeTyVars ty) info'
133                   where
134                     info' | isUserExportedName name = setNoDiscardInfo info
135                           | otherwise               = info
136 \end{code}
137
138 \begin{code}
139 mkVanillaId :: Name -> Type -> Id
140 mkVanillaId name ty = mkId name ty vanillaIdInfo
141
142 -- SysLocal: for an Id being created by the compiler out of thin air...
143 -- UserLocal: an Id with a name the user might recognize...
144 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
145 mkSysLocal  :: UserFS  -> Unique -> Type -> Id
146
147 mkSysLocal  fs uniq ty      = mkVanillaId (mkSysLocalName uniq fs)      ty
148 mkUserLocal occ uniq ty loc = mkVanillaId (mkLocalName    uniq occ loc) ty
149 \end{code}
150
151 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
152 @Uniques@, but that's OK because the templates are supposed to be
153 instantiated before use.
154
155 \begin{code}
156 -- "Wild Id" typically used when you need a binder that you don't expect to use
157 mkWildId :: Type -> Id
158 mkWildId ty = mkSysLocal SLIT("wild") (mkBuiltinUnique 1) ty
159
160 -- "Template locals" typically used in unfoldings
161 mkTemplateLocals :: [Type] -> [Id]
162 mkTemplateLocals tys = zipWith (mkSysLocal SLIT("tpl"))
163                                (getBuiltinUniques (length tys))
164                                tys
165
166 mkTemplateLocal :: Int -> Type -> Id
167 mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
168 \end{code}
169
170
171 %************************************************************************
172 %*                                                                      *
173 \subsection[Id-general-funs]{General @Id@-related functions}
174 %*                                                                      *
175 %************************************************************************
176
177 \begin{code}
178 idFreeTyVars :: Id -> TyVarSet
179 idFreeTyVars id = tyVarsOfType (idType id)
180
181 setIdType :: Id -> Type -> Id
182         -- Add free tyvar info to the type
183 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
184
185 idPrimRep :: Id -> PrimRep
186 idPrimRep id = typePrimRep (idType id)
187 \end{code}
188
189
190 %************************************************************************
191 %*                                                                      *
192 \subsection{Special Ids}
193 %*                                                                      *
194 %************************************************************************
195
196 \begin{code}
197 idFlavour :: Id -> IdFlavour
198 idFlavour id = flavourInfo (idInfo id)
199
200 setIdNoDiscard :: Id -> Id
201 setIdNoDiscard id       -- Make an Id into a NoDiscardId, unless it is already
202   = modifyIdInfo setNoDiscardInfo id
203
204 recordSelectorFieldLabel :: Id -> FieldLabel
205 recordSelectorFieldLabel id = case idFlavour id of
206                                 RecordSelId lbl -> lbl
207
208 isRecordSelector id = case idFlavour id of
209                         RecordSelId lbl -> True
210                         other           -> False
211
212 isPrimOpId id = case idFlavour id of
213                     PrimOpId op -> True
214                     other       -> False
215
216 isPrimOpId_maybe id = case idFlavour id of
217                             PrimOpId op -> Just op
218                             other       -> Nothing
219
220 isDataConId id = case idFlavour id of
221                         DataConId _ -> True
222                         other       -> False
223
224 isDataConId_maybe id = case idFlavour id of
225                           DataConId con -> Just con
226                           other         -> Nothing
227
228 isDataConWrapId_maybe id = case idFlavour id of
229                                   DataConWrapId con -> Just con
230                                   other             -> Nothing
231
232 isDataConWrapId id = case idFlavour id of
233                         DataConWrapId con -> True
234                         other             -> False
235
236 isSpecPragmaId id = case idFlavour id of
237                         SpecPragmaId -> True
238                         other        -> False
239
240 mayHaveNoBinding id = case idFlavour id of
241                         DataConId _ -> True
242                         PrimOpId _  -> True
243                         other       -> False
244         -- mayHaveNoBinding returns True of an Id which may not have a
245         -- binding, even though it is defined in this module.  Notably,
246         -- the constructors of a dictionary are in this situation.
247         --      
248         -- mayHaveNoBinding returns True of some things that *do* have a local binding,
249         -- so it's only an approximation.  That's ok... it's only use for assertions.
250
251 -- Don't drop a binding for an exported Id,
252 -- if it otherwise looks dead.  
253 isExportedId :: Id -> Bool
254 isExportedId id = case idFlavour id of
255                         VanillaId -> False
256                         other     -> True       -- All the others are no-discard
257
258 -- Say if an Id was exported by the user
259 -- Implies isExportedId (see mkId above)
260 isUserExportedId :: Id -> Bool
261 isUserExportedId id = isUserExportedName (idName id)
262 \end{code}
263
264
265 omitIfaceSigForId tells whether an Id's info is implied by other declarations,
266 so we don't need to put its signature in an interface file, even if it's mentioned
267 in some other interface unfolding.
268
269 \begin{code}
270 omitIfaceSigForId :: Id -> Bool
271 omitIfaceSigForId id
272   | isWiredInName (idName id)
273   = True
274
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 = case idOccInfo bndr of
298                                         IAmDead -> True
299                                         other   -> False
300                   | otherwise = False   -- TyVars count as not dead
301
302 isIP id = isIPOcc (getOccName id)
303 \end{code}
304
305
306 %************************************************************************
307 %*                                                                      *
308 \subsection{IdInfo stuff}
309 %*                                                                      *
310 %************************************************************************
311
312 \begin{code}
313         ---------------------------------
314         -- ARITY
315 idArityInfo :: Id -> ArityInfo
316 idArityInfo id = arityInfo (idInfo id)
317
318 idArity :: Id -> Arity
319 idArity id = arityLowerBound (idArityInfo id)
320
321 setIdArityInfo :: Id -> ArityInfo -> Id
322 setIdArityInfo id arity = modifyIdInfo (`setArityInfo` arity) id
323
324         ---------------------------------
325         -- STRICTNESS
326 idStrictness :: Id -> StrictnessInfo
327 idStrictness id = strictnessInfo (idInfo id)
328
329 setIdStrictness :: Id -> StrictnessInfo -> Id
330 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
331
332 -- isBottomingId returns true if an application to n args would diverge
333 isBottomingId :: Id -> Bool
334 isBottomingId id = isBottomingStrictness (idStrictness id)
335
336         ---------------------------------
337         -- WORKER ID
338 idWorkerInfo :: Id -> WorkerInfo
339 idWorkerInfo id = workerInfo (idInfo id)
340
341 setIdWorkerInfo :: Id -> WorkerInfo -> Id
342 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
343
344         ---------------------------------
345         -- UNFOLDING
346 idUnfolding :: Id -> Unfolding
347 idUnfolding id = unfoldingInfo (idInfo id)
348
349 setIdUnfolding :: Id -> Unfolding -> Id
350 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
351
352         ---------------------------------
353         -- DEMAND
354 idDemandInfo :: Id -> Demand
355 idDemandInfo id = demandInfo (idInfo id)
356
357 setIdDemandInfo :: Id -> Demand -> Id
358 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
359
360         ---------------------------------
361         -- UPDATE INFO
362 idUpdateInfo :: Id -> UpdateInfo
363 idUpdateInfo id = updateInfo (idInfo id)
364
365 setIdUpdateInfo :: Id -> UpdateInfo -> Id
366 setIdUpdateInfo id upd_info = modifyIdInfo (`setUpdateInfo` upd_info) id
367
368         ---------------------------------
369         -- SPECIALISATION
370 idSpecialisation :: Id -> CoreRules
371 idSpecialisation id = specInfo (idInfo id)
372
373 setIdSpecialisation :: Id -> CoreRules -> Id
374 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
375
376         ---------------------------------
377         -- CAF INFO
378 idCafInfo :: Id -> CafInfo
379 idCafInfo id = cafInfo (idInfo id)
380
381 setIdCafInfo :: Id -> CafInfo -> Id
382 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
383
384         ---------------------------------
385         -- CPR INFO
386 idCprInfo :: Id -> CprInfo
387 idCprInfo id = cprInfo (idInfo id)
388
389 setIdCprInfo :: Id -> CprInfo -> Id
390 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
391
392         ---------------------------------
393         -- Occcurrence INFO
394 idOccInfo :: Id -> OccInfo
395 idOccInfo id = occInfo (idInfo id)
396
397 setIdOccInfo :: Id -> OccInfo -> Id
398 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
399 \end{code}
400
401
402         ---------------------------------
403         -- INLINING
404 The inline pragma tells us to be very keen to inline this Id, but it's still
405 OK not to if optimisation is switched off.
406
407 \begin{code}
408 idInlinePragma :: Id -> InlinePragInfo
409 idInlinePragma id = inlinePragInfo (idInfo id)
410
411 setInlinePragma :: Id -> InlinePragInfo -> Id
412 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
413
414 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
415 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
416 \end{code}
417
418
419         ---------------------------------
420         -- ONE-SHOT LAMBDAS
421 \begin{code}
422 idLBVarInfo :: Id -> LBVarInfo
423 idLBVarInfo id = lbvarInfo (idInfo id)
424
425 isOneShotLambda :: Id -> Bool
426 isOneShotLambda id = case idLBVarInfo id of
427                         IsOneShotLambda -> True
428                         NoLBVarInfo     -> case splitTyConApp_maybe (idType id) of
429                                                 Just (tycon,_) -> tycon == statePrimTyCon
430                                                 other          -> False
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` IsOneShotLambda) 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