Module header tidyup, phase 1
[ghc-hetmet.git] / compiler / basicTypes / Id.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5 \section[Id]{@Ids@: Value and constructor identifiers}
6
7 \begin{code}
8 module Id (
9         Id, DictId,
10
11         -- Simple construction
12         mkGlobalId, mkLocalId, mkLocalIdWithInfo, 
13         mkSysLocal, mkUserLocal, mkVanillaGlobal,
14         mkTemplateLocals, mkTemplateLocalsNum, mkWildId, mkTemplateLocal,
15         mkWorkerId, mkExportedLocalId,
16
17         -- Taking an Id apart
18         idName, idType, idUnique, idInfo,
19         isId, globalIdDetails, idPrimRep,
20         recordSelectorFieldLabel,
21
22         -- Modifying an Id
23         setIdName, setIdUnique, Id.setIdType, setIdExported, setIdNotExported, 
24         setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo,
25         zapLamIdInfo, zapDemandIdInfo, 
26
27         -- Predicates
28         isImplicitId, isDeadBinder, isDictId,
29         isExportedId, isLocalId, isGlobalId,
30         isRecordSelector, isNaughtyRecordSelector,
31         isClassOpId_maybe,
32         isPrimOpId, isPrimOpId_maybe, 
33         isFCallId, isFCallId_maybe,
34         isDataConWorkId, isDataConWorkId_maybe, isDataConId_maybe, idDataCon,
35         isBottomingId, idIsFrom,
36         hasNoBinding, 
37
38         -- Inline pragma stuff
39         idInlinePragma, setInlinePragma, modifyInlinePragma, 
40
41
42         -- One shot lambda stuff
43         isOneShotBndr, isOneShotLambda, isStateHackType,
44         setOneShotLambda, clearOneShotLambda,
45
46         -- IdInfo stuff
47         setIdUnfolding,
48         setIdArity,
49         setIdNewDemandInfo, 
50         setIdNewStrictness, zapIdNewStrictness,
51         setIdWorkerInfo,
52         setIdSpecialisation,
53         setIdCafInfo,
54         setIdOccInfo,
55
56 #ifdef OLD_STRICTNESS
57         idDemandInfo, 
58         idStrictness, 
59         idCprInfo,
60         setIdStrictness, 
61         setIdDemandInfo, 
62         setIdCprInfo,
63 #endif
64
65         idArity, 
66         idNewDemandInfo, idNewDemandInfo_maybe,
67         idNewStrictness, idNewStrictness_maybe, 
68         idWorkerInfo,
69         idUnfolding,
70         idSpecialisation, idCoreRules, idHasRules,
71         idCafInfo,
72         idLBVarInfo,
73         idOccInfo,
74
75 #ifdef OLD_STRICTNESS
76         newStrictnessFromOld    -- Temporary
77 #endif
78
79     ) where
80
81 #include "HsVersions.h"
82
83 import CoreSyn
84 import BasicTypes
85 import qualified Var
86 import Var hiding (mkLocalId, mkGlobalId, mkExportedLocalId)
87 import TyCon
88 import Type
89 import TcType
90 import TysPrim
91 import IdInfo 
92 #ifdef OLD_STRICTNESS
93 import qualified Demand
94 #endif
95 import DataCon
96 import NewDemand
97 import Name
98 import Module
99 import OccName
100 import Maybes
101 import SrcLoc
102 import Outputable
103 import Unique
104 import FastString
105 import StaticFlags
106
107 -- infixl so you can say (id `set` a `set` b)
108 infixl  1 `setIdUnfolding`,
109           `setIdArity`,
110           `setIdNewDemandInfo`,
111           `setIdNewStrictness`,
112           `setIdWorkerInfo`,
113           `setIdSpecialisation`,
114           `setInlinePragma`,
115           `idCafInfo`
116 #ifdef OLD_STRICTNESS
117           ,`idCprInfo`
118           ,`setIdStrictness`
119           ,`setIdDemandInfo`
120 #endif
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 is just like Var.mkId,
132 but in addition it pins free-tyvar-info onto the Id's type, 
133 where it can easily be found.
134
135 \begin{code}
136 mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id
137 mkLocalIdWithInfo name ty info = Var.mkLocalId name (addFreeTyVars ty) info
138
139 mkExportedLocalId :: Name -> Type -> Id
140 mkExportedLocalId name ty = Var.mkExportedLocalId name (addFreeTyVars ty) vanillaIdInfo
141
142 mkGlobalId :: GlobalIdDetails -> Name -> Type -> IdInfo -> Id
143 mkGlobalId details name ty info = Var.mkGlobalId details name (addFreeTyVars ty) info
144 \end{code}
145
146 \begin{code}
147 mkLocalId :: Name -> Type -> Id
148 mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo
149
150 -- SysLocal: for an Id being created by the compiler out of thin air...
151 mkSysLocal :: FastString -> Unique -> Type -> Id
152 mkSysLocal fs uniq ty = mkLocalId (mkSystemVarName uniq fs) ty
153
154
155 -- UserLocal: an Id with a name the user might recognize...
156 mkUserLocal :: OccName -> Unique -> Type -> SrcLoc -> Id
157 mkVanillaGlobal :: Name -> Type -> IdInfo -> Id
158
159 mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName    uniq occ loc) ty
160 mkVanillaGlobal             = mkGlobalId VanillaGlobal
161 \end{code}
162
163 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
164 @Uniques@, but that's OK because the templates are supposed to be
165 instantiated before use.
166  
167 \begin{code}
168 -- "Wild Id" typically used when you need a binder that you don't expect to use
169 mkWildId :: Type -> Id
170 mkWildId ty = mkSysLocal FSLIT("wild") (mkBuiltinUnique 1) ty
171
172 mkWorkerId :: Unique -> Id -> Type -> Id
173 -- A worker gets a local name.  CoreTidy will externalise it if necessary.
174 mkWorkerId uniq unwrkr ty
175   = mkLocalId wkr_name ty
176   where
177     wkr_name = mkInternalName uniq (mkWorkerOcc (getOccName unwrkr)) (getSrcLoc unwrkr)
178
179 -- "Template locals" typically used in unfoldings
180 mkTemplateLocals :: [Type] -> [Id]
181 mkTemplateLocals tys = zipWith mkTemplateLocal [1..] tys
182
183 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
184 -- The Int gives the starting point for unique allocation
185 mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys
186
187 mkTemplateLocal :: Int -> Type -> Id
188 mkTemplateLocal i ty = mkSysLocal FSLIT("tpl") (mkBuiltinUnique i) ty
189 \end{code}
190
191
192 %************************************************************************
193 %*                                                                      *
194 \subsection[Id-general-funs]{General @Id@-related functions}
195 %*                                                                      *
196 %************************************************************************
197
198 \begin{code}
199 setIdType :: Id -> Type -> Id
200         -- Add free tyvar info to the type
201 setIdType id ty = seqType ty `seq` Var.setIdType id (addFreeTyVars ty)
202
203 idPrimRep :: Id -> PrimRep
204 idPrimRep id = typePrimRep (idType id)
205 \end{code}
206
207
208 %************************************************************************
209 %*                                                                      *
210 \subsection{Special Ids}
211 %*                                                                      *
212 %************************************************************************
213
214 \begin{code}
215 recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel)
216 recordSelectorFieldLabel id = case globalIdDetails id of
217                                  RecordSelId tycon lbl _ -> (tycon,lbl)
218                                  other -> panic "recordSelectorFieldLabel"
219
220 isRecordSelector id = case globalIdDetails id of
221                         RecordSelId {}  -> True
222                         other           -> False
223
224 isNaughtyRecordSelector id = case globalIdDetails id of
225                         RecordSelId { sel_naughty = n } -> n
226                         other                           -> False
227
228 isClassOpId_maybe id = case globalIdDetails id of
229                         ClassOpId cls -> Just cls
230                         _other        -> Nothing
231
232 isPrimOpId id = case globalIdDetails id of
233                     PrimOpId op -> True
234                     other       -> False
235
236 isPrimOpId_maybe id = case globalIdDetails id of
237                             PrimOpId op -> Just op
238                             other       -> Nothing
239
240 isFCallId id = case globalIdDetails id of
241                     FCallId call -> True
242                     other        -> False
243
244 isFCallId_maybe id = case globalIdDetails id of
245                             FCallId call -> Just call
246                             other        -> Nothing
247
248 isDataConWorkId id = case globalIdDetails id of
249                         DataConWorkId _ -> True
250                         other           -> False
251
252 isDataConWorkId_maybe id = case globalIdDetails id of
253                           DataConWorkId con -> Just con
254                           other             -> Nothing
255
256 isDataConId_maybe :: Id -> Maybe DataCon
257 isDataConId_maybe id = case globalIdDetails id of
258                          DataConWorkId con -> Just con
259                          DataConWrapId con -> Just con
260                          other              -> Nothing
261
262 idDataCon :: Id -> DataCon
263 -- Get from either the worker or the wrapper to the DataCon
264 -- Currently used only in the desugarer
265 --       INVARIANT: idDataCon (dataConWrapId d) = d
266 -- (Remember, dataConWrapId can return either the wrapper or the worker.)
267 idDataCon id = case globalIdDetails id of
268                   DataConWorkId con -> con
269                   DataConWrapId con -> con
270                   other             -> pprPanic "idDataCon" (ppr id)
271
272
273 isDictId :: Id -> Bool
274 isDictId id = isDictTy (idType id)
275
276 -- hasNoBinding returns True of an Id which may not have a
277 -- binding, even though it is defined in this module.  
278 -- Data constructor workers used to be things of this kind, but
279 -- they aren't any more.  Instead, we inject a binding for 
280 -- them at the CorePrep stage. 
281 -- EXCEPT: unboxed tuples, which definitely have no binding
282 hasNoBinding id = case globalIdDetails id of
283                         PrimOpId _       -> True
284                         FCallId _        -> True
285                         DataConWorkId dc -> isUnboxedTupleCon dc
286                         other            -> False
287
288 isImplicitId :: Id -> Bool
289         -- isImplicitId tells whether an Id's info is implied by other
290         -- declarations, so we don't need to put its signature in an interface
291         -- file, even if it's mentioned in some other interface unfolding.
292 isImplicitId id
293   = case globalIdDetails id of
294         RecordSelId {}  -> True
295         FCallId _       -> True
296         PrimOpId _      -> True
297         ClassOpId _     -> True
298         DataConWorkId _ -> True
299         DataConWrapId _ -> True
300                 -- These are are implied by their type or class decl;
301                 -- remember that all type and class decls appear in the interface file.
302                 -- The dfun id is not an implicit Id; it must *not* be omitted, because 
303                 -- it carries version info for the instance decl
304         other           -> False
305
306 idIsFrom :: Module -> Id -> Bool
307 idIsFrom mod id = nameIsLocalOrFrom mod (idName id)
308 \end{code}
309
310 \begin{code}
311 isDeadBinder :: Id -> Bool
312 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
313                   | otherwise = False   -- TyVars count as not dead
314 \end{code}
315
316
317 %************************************************************************
318 %*                                                                      *
319 \subsection{IdInfo stuff}
320 %*                                                                      *
321 %************************************************************************
322
323 \begin{code}
324         ---------------------------------
325         -- ARITY
326 idArity :: Id -> Arity
327 idArity id = arityInfo (idInfo id)
328
329 setIdArity :: Id -> Arity -> Id
330 setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id
331
332 #ifdef OLD_STRICTNESS
333         ---------------------------------
334         -- (OLD) STRICTNESS 
335 idStrictness :: Id -> StrictnessInfo
336 idStrictness id = strictnessInfo (idInfo id)
337
338 setIdStrictness :: Id -> StrictnessInfo -> Id
339 setIdStrictness id strict_info = modifyIdInfo (`setStrictnessInfo` strict_info) id
340 #endif
341
342 -- isBottomingId returns true if an application to n args would diverge
343 isBottomingId :: Id -> Bool
344 isBottomingId id = isBottomingSig (idNewStrictness id)
345
346 idNewStrictness_maybe :: Id -> Maybe StrictSig
347 idNewStrictness :: Id -> StrictSig
348
349 idNewStrictness_maybe id = newStrictnessInfo (idInfo id)
350 idNewStrictness       id = idNewStrictness_maybe id `orElse` topSig
351
352 setIdNewStrictness :: Id -> StrictSig -> Id
353 setIdNewStrictness id sig = modifyIdInfo (`setNewStrictnessInfo` Just sig) id
354
355 zapIdNewStrictness :: Id -> Id
356 zapIdNewStrictness id = modifyIdInfo (`setNewStrictnessInfo` Nothing) id
357
358         ---------------------------------
359         -- WORKER ID
360 idWorkerInfo :: Id -> WorkerInfo
361 idWorkerInfo id = workerInfo (idInfo id)
362
363 setIdWorkerInfo :: Id -> WorkerInfo -> Id
364 setIdWorkerInfo id work_info = modifyIdInfo (`setWorkerInfo` work_info) id
365
366         ---------------------------------
367         -- UNFOLDING
368 idUnfolding :: Id -> Unfolding
369 idUnfolding id = unfoldingInfo (idInfo id)
370
371 setIdUnfolding :: Id -> Unfolding -> Id
372 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
373
374 #ifdef OLD_STRICTNESS
375         ---------------------------------
376         -- (OLD) DEMAND
377 idDemandInfo :: Id -> Demand.Demand
378 idDemandInfo id = demandInfo (idInfo id)
379
380 setIdDemandInfo :: Id -> Demand.Demand -> Id
381 setIdDemandInfo id demand_info = modifyIdInfo (`setDemandInfo` demand_info) id
382 #endif
383
384 idNewDemandInfo_maybe :: Id -> Maybe NewDemand.Demand
385 idNewDemandInfo       :: Id -> NewDemand.Demand
386
387 idNewDemandInfo_maybe id = newDemandInfo (idInfo id)
388 idNewDemandInfo       id = newDemandInfo (idInfo id) `orElse` NewDemand.topDmd
389
390 setIdNewDemandInfo :: Id -> NewDemand.Demand -> Id
391 setIdNewDemandInfo id dmd = modifyIdInfo (`setNewDemandInfo` Just dmd) id
392
393         ---------------------------------
394         -- SPECIALISATION
395 idSpecialisation :: Id -> SpecInfo
396 idSpecialisation id = specInfo (idInfo id)
397
398 idCoreRules :: Id -> [CoreRule]
399 idCoreRules id = specInfoRules (idSpecialisation id)
400
401 idHasRules :: Id -> Bool
402 idHasRules id = not (isEmptySpecInfo (idSpecialisation id))
403
404 setIdSpecialisation :: Id -> SpecInfo -> Id
405 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
406
407         ---------------------------------
408         -- CAF INFO
409 idCafInfo :: Id -> CafInfo
410 #ifdef OLD_STRICTNESS
411 idCafInfo id = case cgInfo (idInfo id) of
412                   NoCgInfo -> pprPanic "idCafInfo" (ppr id)
413                   info     -> cgCafInfo info
414 #else
415 idCafInfo id = cafInfo (idInfo id)
416 #endif
417
418 setIdCafInfo :: Id -> CafInfo -> Id
419 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
420
421         ---------------------------------
422         -- CPR INFO
423 #ifdef OLD_STRICTNESS
424 idCprInfo :: Id -> CprInfo
425 idCprInfo id = cprInfo (idInfo id)
426
427 setIdCprInfo :: Id -> CprInfo -> Id
428 setIdCprInfo id cpr_info = modifyIdInfo (`setCprInfo` cpr_info) id
429 #endif
430
431         ---------------------------------
432         -- Occcurrence INFO
433 idOccInfo :: Id -> OccInfo
434 idOccInfo id = occInfo (idInfo id)
435
436 setIdOccInfo :: Id -> OccInfo -> Id
437 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
438 \end{code}
439
440
441         ---------------------------------
442         -- INLINING
443 The inline pragma tells us to be very keen to inline this Id, but it's still
444 OK not to if optimisation is switched off.
445
446 \begin{code}
447 idInlinePragma :: Id -> InlinePragInfo
448 idInlinePragma id = inlinePragInfo (idInfo id)
449
450 setInlinePragma :: Id -> InlinePragInfo -> Id
451 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
452
453 modifyInlinePragma :: Id -> (InlinePragInfo -> InlinePragInfo) -> Id
454 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
455 \end{code}
456
457
458         ---------------------------------
459         -- ONE-SHOT LAMBDAS
460 \begin{code}
461 idLBVarInfo :: Id -> LBVarInfo
462 idLBVarInfo id = lbvarInfo (idInfo id)
463
464 isOneShotBndr :: Id -> Bool
465 -- This one is the "business end", called externally.
466 -- Its main purpose is to encapsulate the Horrible State Hack
467 isOneShotBndr id = isOneShotLambda id || isStateHackType (idType id)
468
469 isStateHackType :: Type -> Bool
470 isStateHackType ty
471   | opt_NoStateHack 
472   = False
473   | otherwise
474   = case splitTyConApp_maybe ty of
475         Just (tycon,_) -> tycon == statePrimTyCon
476         other          -> False
477         -- This is a gross hack.  It claims that 
478         -- every function over realWorldStatePrimTy is a one-shot
479         -- function.  This is pretty true in practice, and makes a big
480         -- difference.  For example, consider
481         --      a `thenST` \ r -> ...E...
482         -- The early full laziness pass, if it doesn't know that r is one-shot
483         -- will pull out E (let's say it doesn't mention r) to give
484         --      let lvl = E in a `thenST` \ r -> ...lvl...
485         -- When `thenST` gets inlined, we end up with
486         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
487         -- and we don't re-inline E.
488         --
489         -- It would be better to spot that r was one-shot to start with, but
490         -- I don't want to rely on that.
491         --
492         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
493         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
494
495
496 -- The OneShotLambda functions simply fiddle with the IdInfo flag
497 isOneShotLambda :: Id -> Bool
498 isOneShotLambda id = case idLBVarInfo id of
499                        IsOneShotLambda  -> True
500                        NoLBVarInfo      -> False
501
502 setOneShotLambda :: Id -> Id
503 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
504
505 clearOneShotLambda :: Id -> Id
506 clearOneShotLambda id 
507   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
508   | otherwise          = id                     
509
510 -- But watch out: this may change the type of something else
511 --      f = \x -> e
512 -- If we change the one-shot-ness of x, f's type changes
513 \end{code}
514
515 \begin{code}
516 zapLamIdInfo :: Id -> Id
517 zapLamIdInfo id = maybeModifyIdInfo (zapLamInfo (idInfo id)) id
518
519 zapDemandIdInfo id = maybeModifyIdInfo (zapDemandInfo (idInfo id)) id
520 \end{code}
521