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