[project @ 2000-10-12 14:41:15 by simonmar]
[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, CoreExpr, Expr(..),
74                           AltCon (..), Alt, mkApps, Arg )
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, 
81                           maybeModifyIdInfo,
82                           externallyVisibleId
83                         )
84 import VarSet
85 import Type             ( Type, tyVarsOfType, typePrimRep, addFreeTyVars, 
86                           seqType, splitAlgTyConApp_maybe, mkTyVarTy,
87                           mkTyConApp, splitTyConApp_maybe)
88
89 import IdInfo 
90
91 import Demand           ( Demand, isStrict, wwLazy )
92 import Name             ( Name, OccName,
93                           mkSysLocalName, mkLocalName,
94                           isUserExportedName, getOccName, isIPOcc
95                         ) 
96 import OccName          ( UserFS )
97 import PrimRep          ( PrimRep )
98 import PrimOp           ( PrimOp, primOpIsCheap )
99 import TysPrim          ( statePrimTyCon )
100 import FieldLabel       ( FieldLabel )
101 import SrcLoc           ( SrcLoc )
102 import Unique           ( Unique, mkBuiltinUnique, getBuiltinUniques, 
103                           getNumBuiltinUniques )
104 import Outputable
105 import TyCon            ( TyCon, AlgTyConFlavour(..), ArgVrcs, mkSynTyCon, 
106                           mkAlgTyConRep, tyConName, 
107                           tyConTyVars, tyConDataCons )
108 import DataCon          ( DataCon, dataConWrapId, dataConOrigArgTys )
109 import Var              ( Var )
110 infixl  1 `setIdUnfolding`,
111           `setIdArityInfo`,
112           `setIdDemandInfo`,
113           `setIdStrictness`,
114           `setIdWorkerInfo`,
115           `setIdSpecialisation`,
116           `setInlinePragma`,
117           `idCafInfo`,
118           `idCprInfo`
119
120         -- infixl so you can say (id `set` a `set` b)
121 \end{code}
122
123
124
125 %************************************************************************
126 %*                                                                      *
127 \subsection{Simple Id construction}
128 %*                                                                      *
129 %************************************************************************
130
131 Absolutely all Ids are made by mkId.  It 
132         a) Pins free-tyvar-info onto the Id's type, 
133            where it can easily be found.
134         b) Ensures that exported Ids are 
135
136 \begin{code}
137 mkId :: Name -> Type -> IdInfo -> Id
138 mkId name ty info = mkIdVar name (addFreeTyVars ty) info'
139                   where
140                     info' | isUserExportedName name = setNoDiscardInfo info
141                           | otherwise               = info
142 \end{code}
143
144 \begin{code}
145 mkVanillaId :: Name -> Type -> Id
146 mkVanillaId name ty = mkId name ty vanillaIdInfo
147
148 -- SysLocal: for an Id being created by the compiler out of thin air...
149 -- UserLocal: an Id with a name the user might recognize...
150 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
151 mkSysLocal  :: UserFS  -> Unique -> Type -> Id
152
153 mkSysLocal  fs uniq ty      = mkVanillaId (mkSysLocalName uniq fs)      ty
154 mkUserLocal occ uniq ty loc = mkVanillaId (mkLocalName    uniq occ loc) ty
155 \end{code}
156
157 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
158 @Uniques@, but that's OK because the templates are supposed to be
159 instantiated before use.
160
161 \begin{code}
162 -- "Wild Id" typically used when you need a binder that you don't expect to use
163 mkWildId :: Type -> Id
164 mkWildId ty = mkSysLocal SLIT("wild") (mkBuiltinUnique 1) ty
165
166 -- "Template locals" typically used in unfoldings
167 mkTemplateLocals :: [Type] -> [Id]
168 mkTemplateLocals tys = zipWith (mkSysLocal SLIT("tpl"))
169                                (getBuiltinUniques (length tys))
170                                tys
171
172 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
173 mkTemplateLocalsNum n tys = zipWith (mkSysLocal SLIT("tpl"))
174                                (getNumBuiltinUniques n (length tys))
175                                tys
176
177 mkTemplateLocal :: Int -> Type -> Id
178 mkTemplateLocal i ty = mkSysLocal SLIT("tpl") (mkBuiltinUnique i) ty
179 \end{code}
180
181
182 %************************************************************************
183 %*                                                                      *
184 \subsection[Id-general-funs]{General @Id@-related functions}
185 %*                                                                      *
186 %************************************************************************
187
188 \begin{code}
189 idFreeTyVars :: Id -> TyVarSet
190 idFreeTyVars id = tyVarsOfType (idType id)
191
192 setIdType :: Id -> Type -> Id
193         -- Add free tyvar info to the type
194 setIdType id ty = seqType ty `seq` setVarType id (addFreeTyVars ty)
195
196 idPrimRep :: Id -> PrimRep
197 idPrimRep id = typePrimRep (idType id)
198 \end{code}
199
200
201 %************************************************************************
202 %*                                                                      *
203 \subsection{Special Ids}
204 %*                                                                      *
205 %************************************************************************
206
207 \begin{code}
208 idFlavour :: Id -> IdFlavour
209 idFlavour id = flavourInfo (idInfo id)
210
211 setIdNoDiscard :: Id -> Id
212 setIdNoDiscard id       -- Make an Id into a NoDiscardId, unless it is already
213   = modifyIdInfo setNoDiscardInfo id
214
215 recordSelectorFieldLabel :: Id -> FieldLabel
216 recordSelectorFieldLabel id = case idFlavour id of
217                                 RecordSelId lbl -> lbl
218
219 isRecordSelector id = case idFlavour id of
220                         RecordSelId lbl -> True
221                         other           -> False
222
223 isPrimOpId id = case idFlavour id of
224                     PrimOpId op -> True
225                     other       -> False
226
227 isPrimOpId_maybe id = case idFlavour id of
228                             PrimOpId op -> Just op
229                             other       -> Nothing
230
231 isDataConId id = case idFlavour id of
232                         DataConId _ -> True
233                         other       -> False
234
235 isDataConId_maybe id = case idFlavour id of
236                           DataConId con -> Just con
237                           other         -> Nothing
238
239 isDataConWrapId_maybe id = case idFlavour id of
240                                   DataConWrapId con -> Just con
241                                   other             -> Nothing
242
243 isDataConWrapId id = case idFlavour id of
244                         DataConWrapId con -> True
245                         other             -> False
246
247 isSpecPragmaId id = case idFlavour id of
248                         SpecPragmaId -> True
249                         other        -> False
250
251 hasNoBinding id = case idFlavour id of
252                         DataConId _ -> True
253                         PrimOpId _  -> True
254                         other       -> False
255         -- hasNoBinding returns True of an Id which may not have a
256         -- binding, even though it is defined in this module.  Notably,
257         -- the constructors of a dictionary are in this situation.
258
259 -- Don't drop a binding for an exported Id,
260 -- if it otherwise looks dead.  
261 isExportedId :: Id -> Bool
262 isExportedId id = case idFlavour id of
263                         VanillaId -> False
264                         other     -> True       -- All the others are no-discard
265
266 -- Say if an Id was exported by the user
267 -- Implies isExportedId (see mkId above)
268 isUserExportedId :: Id -> Bool
269 isUserExportedId id = isUserExportedName (idName id)
270 \end{code}
271
272
273 omitIfaceSigForId tells whether an Id's info is implied by other declarations,
274 so we don't need to put its signature in an interface file, even if it's mentioned
275 in some other interface unfolding.
276
277 \begin{code}
278 omitIfaceSigForId :: Id -> Bool
279 omitIfaceSigForId id
280   | otherwise
281   = case idFlavour id of
282         RecordSelId _   -> True -- Includes dictionary selectors
283         PrimOpId _      -> True
284         DataConId _     -> True
285         DataConWrapId _ -> True
286                 -- These are are implied by their type or class decl;
287                 -- remember that all type and class decls appear in the interface file.
288                 -- The dfun id must *not* be omitted, because it carries version info for
289                 -- the instance decl
290
291         other          -> False -- Don't omit!
292
293 -- Certain names must be exported with their original occ names, because
294 -- these names are bound by either a class declaration or a data declaration
295 -- or an explicit user export.
296 exportWithOrigOccName :: Id -> Bool
297 exportWithOrigOccName id = omitIfaceSigForId id || isUserExportedId id
298 \end{code}
299
300 \begin{code}
301 isDeadBinder :: Id -> Bool
302 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
303                   | otherwise = False   -- TyVars count as not dead
304
305 isIP id = isIPOcc (getOccName id)
306 \end{code}
307
308
309 %************************************************************************
310 %*                                                                      *
311 \subsection{IdInfo stuff}
312 %*                                                                      *
313 %************************************************************************
314
315 \begin{code}
316         ---------------------------------
317         -- ARITY
318 idArityInfo :: Id -> ArityInfo
319 idArityInfo id = arityInfo (idInfo id)
320
321 idArity :: Id -> Arity
322 idArity id = arityLowerBound (idArityInfo id)
323
324 setIdArityInfo :: Id -> ArityInfo -> Id
325 setIdArityInfo id arity = modifyIdInfo (`setArityInfo` arity) id
326
327         ---------------------------------
328         -- STRICTNESS
329 idStrictness :: Id -> StrictnessInfo
330 idStrictness id = strictnessInfo (idInfo id)
331
332 setIdStrictness :: Id -> StrictnessInfo -> Id
333 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
334
335 -- isBottomingId returns true if an application to n args would diverge
336 isBottomingId :: Id -> Bool
337 isBottomingId id = isBottomingStrictness (idStrictness 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 = case idLBVarInfo id of
422                         IsOneShotLambda -> True
423                         NoLBVarInfo     -> case splitTyConApp_maybe (idType id) of
424                                                 Just (tycon,_) -> tycon == statePrimTyCon
425                                                 other          -> False
426         -- The last clause is a gross hack.  It claims that 
427         -- every function over realWorldStatePrimTy is a one-shot
428         -- function.  This is pretty true in practice, and makes a big
429         -- difference.  For example, consider
430         --      a `thenST` \ r -> ...E...
431         -- The early full laziness pass, if it doesn't know that r is one-shot
432         -- will pull out E (let's say it doesn't mention r) to give
433         --      let lvl = E in a `thenST` \ r -> ...lvl...
434         -- When `thenST` gets inlined, we end up with
435         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
436         -- and we don't re-inline E.
437         --
438         -- It would be better to spot that r was one-shot to start with, but
439         -- I don't want to rely on that.
440         --
441         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
442         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
443
444 setOneShotLambda :: Id -> Id
445 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
446
447 clearOneShotLambda :: Id -> Id
448 clearOneShotLambda id 
449   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
450   | otherwise          = id                     
451
452 -- But watch out: this may change the type of something else
453 --      f = \x -> e
454 -- If we change the one-shot-ness of x, f's type changes
455 \end{code}
456
457 \begin{code}
458 zapFragileIdInfo :: Id -> Id
459 zapFragileIdInfo id = maybeModifyIdInfo zapFragileInfo id
460
461 zapLamIdInfo :: Id -> Id
462 zapLamIdInfo id = maybeModifyIdInfo zapLamInfo id
463 \end{code}
464
465
466
467
468
469
470
471
472
473
474