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