fbf6b4a25644ba63f9fc95c7a86680152d4631c1
[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 -- |
9 -- #name_types#
10 -- GHC uses several kinds of name internally:
11 --
12 -- * 'OccName.OccName': see "OccName#name_types"
13 --
14 -- * 'RdrName.RdrName': see "RdrName#name_types"
15 --
16 -- * 'Name.Name': see "Name#name_types"
17 --
18 -- * 'Id.Id' represents names that not only have a 'Name.Name' but also a 'TypeRep.Type' and some additional
19 --   details (a 'IdInfo.IdInfo' and one of 'Var.LocalIdDetails' or 'IdInfo.GlobalIdDetails') that
20 --   are added, modified and inspected by various compiler passes. These 'Var.Var' names may either 
21 --   be global or local, see "Var#globalvslocal"
22 --
23 -- * 'Var.Var': see "Var#name_types"
24 module Id (
25         -- * The main types
26         Id, DictId,
27
28         -- ** Simple construction
29         mkGlobalId, mkVanillaGlobal, mkVanillaGlobalWithInfo,
30         mkLocalId, mkLocalIdWithInfo, mkExportedLocalId,
31         mkSysLocal, mkSysLocalM, mkUserLocal, mkUserLocalM,
32         mkTemplateLocals, mkTemplateLocalsNum, mkTemplateLocal,
33         mkWorkerId, 
34
35         -- ** Taking an Id apart
36         idName, idType, idUnique, idInfo, idDetails,
37         isId, idPrimRep,
38         recordSelectorFieldLabel,
39
40         -- ** Modifying an Id
41         setIdName, setIdUnique, Id.setIdType, 
42         setIdExported, setIdNotExported, 
43         globaliseId, localiseId, 
44         setIdInfo, lazySetIdInfo, modifyIdInfo, maybeModifyIdInfo,
45         zapLamIdInfo, zapDemandIdInfo, zapFragileIdInfo, transferPolyIdInfo,
46         
47
48         -- ** Predicates on Ids
49         isImplicitId, isDeadBinder, isDictId, isStrictId,
50         isExportedId, isLocalId, isGlobalId,
51         isRecordSelector, isNaughtyRecordSelector,
52         isClassOpId_maybe, isDFunId,
53         isPrimOpId, isPrimOpId_maybe, 
54         isFCallId, isFCallId_maybe,
55         isDataConWorkId, isDataConWorkId_maybe, isDataConId_maybe, idDataCon,
56         isConLikeId, isBottomingId, idIsFrom,
57         isTickBoxOp, isTickBoxOp_maybe,
58         hasNoBinding, 
59
60         -- ** Inline pragma stuff
61         idInlinePragma, setInlinePragma, modifyInlinePragma,
62         idInlineActivation, setInlineActivation, idRuleMatchInfo,
63
64         -- ** One-shot lambdas
65         isOneShotBndr, isOneShotLambda, isStateHackType,
66         setOneShotLambda, clearOneShotLambda,
67
68         -- ** Reading 'IdInfo' fields
69         idArity, 
70         idDemandInfo, idDemandInfo_maybe,
71         idStrictness, idStrictness_maybe, 
72         idUnfolding, realIdUnfolding,
73         idSpecialisation, idCoreRules, idHasRules,
74         idCafInfo,
75         idLBVarInfo,
76         idOccInfo,
77
78         -- ** Writing 'IdInfo' fields
79         setIdUnfolding,
80         setIdArity,
81         setIdDemandInfo, 
82         setIdStrictness, zapIdStrictness,
83         setIdSpecialisation,
84         setIdCafInfo,
85         setIdOccInfo, zapIdOccInfo,
86
87     ) where
88
89 #include "HsVersions.h"
90
91 import CoreSyn ( CoreRule, Unfolding( NoUnfolding ) )
92
93 import IdInfo
94 import BasicTypes
95
96 -- Imported and re-exported 
97 import Var( Var, Id, DictId,
98             idInfo, idDetails, globaliseId,
99             isId, isLocalId, isGlobalId, isExportedId )
100 import qualified Var
101
102 import TyCon
103 import Type
104 import TysPrim
105 import DataCon
106 import Demand
107 import Name
108 import Module
109 import Class
110 import PrimOp
111 import ForeignCall
112 import Maybes
113 import SrcLoc
114 import Outputable
115 import Unique
116 import UniqSupply
117 import FastString
118 import Util( count )
119 import StaticFlags
120
121 -- infixl so you can say (id `set` a `set` b)
122 infixl  1 `setIdUnfolding`,
123           `setIdArity`,
124           `setIdOccInfo`,
125           `setIdDemandInfo`,
126           `setIdStrictness`,
127           `setIdSpecialisation`,
128           `setInlinePragma`,
129           `setInlineActivation`,
130           `idCafInfo`
131 \end{code}
132
133 %************************************************************************
134 %*                                                                      *
135 \subsection{Basic Id manipulation}
136 %*                                                                      *
137 %************************************************************************
138
139 \begin{code}
140 idName   :: Id -> Name
141 idName    = Var.varName
142
143 idUnique :: Id -> Unique
144 idUnique  = Var.varUnique
145
146 idType   :: Id -> Kind
147 idType    = Var.varType
148
149 idPrimRep :: Id -> PrimRep
150 idPrimRep id = typePrimRep (idType id)
151
152 setIdName :: Id -> Name -> Id
153 setIdName = Var.setVarName
154
155 setIdUnique :: Id -> Unique -> Id
156 setIdUnique = Var.setVarUnique
157
158 -- | Not only does this set the 'Id' 'Type', it also evaluates the type to try and
159 -- reduce space usage
160 setIdType :: Id -> Type -> Id
161 setIdType id ty = seqType ty `seq` Var.setVarType id ty
162
163 setIdExported :: Id -> Id
164 setIdExported = Var.setIdExported
165
166 setIdNotExported :: Id -> Id
167 setIdNotExported = Var.setIdNotExported
168
169 localiseId :: Id -> Id
170 -- Make an with the same unique and type as the 
171 -- incoming Id, but with an *Internal* Name and *LocalId* flavour
172 localiseId id 
173   | isLocalId id && isInternalName name
174   = id
175   | otherwise
176   = mkLocalIdWithInfo (localiseName name) (idType id) (idInfo id)
177   where
178     name = idName id
179
180 lazySetIdInfo :: Id -> IdInfo -> Id
181 lazySetIdInfo = Var.lazySetIdInfo
182
183 setIdInfo :: Id -> IdInfo -> Id
184 setIdInfo id info = seqIdInfo info `seq` (lazySetIdInfo id info)
185         -- Try to avoid spack leaks by seq'ing
186
187 modifyIdInfo :: (IdInfo -> IdInfo) -> Id -> Id
188 modifyIdInfo fn id = setIdInfo id (fn (idInfo id))
189
190 -- maybeModifyIdInfo tries to avoid unnecesary thrashing
191 maybeModifyIdInfo :: Maybe IdInfo -> Id -> Id
192 maybeModifyIdInfo (Just new_info) id = lazySetIdInfo id new_info
193 maybeModifyIdInfo Nothing         id = id
194 \end{code}
195
196 %************************************************************************
197 %*                                                                      *
198 \subsection{Simple Id construction}
199 %*                                                                      *
200 %************************************************************************
201
202 Absolutely all Ids are made by mkId.  It is just like Var.mkId,
203 but in addition it pins free-tyvar-info onto the Id's type, 
204 where it can easily be found.
205
206 Note [Free type variables]
207 ~~~~~~~~~~~~~~~~~~~~~~~~~~
208 At one time we cached the free type variables of the type of an Id
209 at the root of the type in a TyNote.  The idea was to avoid repeating
210 the free-type-variable calculation.  But it turned out to slow down
211 the compiler overall. I don't quite know why; perhaps finding free
212 type variables of an Id isn't all that common whereas applying a 
213 substitution (which changes the free type variables) is more common.
214 Anyway, we removed it in March 2008.
215
216 \begin{code}
217 -- | For an explanation of global vs. local 'Id's, see "Var#globalvslocal"
218 mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id
219 mkGlobalId = Var.mkGlobalVar
220
221 -- | Make a global 'Id' without any extra information at all
222 mkVanillaGlobal :: Name -> Type -> Id
223 mkVanillaGlobal name ty = mkVanillaGlobalWithInfo name ty vanillaIdInfo
224
225 -- | Make a global 'Id' with no global information but some generic 'IdInfo'
226 mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id
227 mkVanillaGlobalWithInfo = mkGlobalId VanillaId
228
229
230 -- | For an explanation of global vs. local 'Id's, see "Var#globalvslocal"
231 mkLocalId :: Name -> Type -> Id
232 mkLocalId name ty = mkLocalIdWithInfo name ty vanillaIdInfo
233
234 mkLocalIdWithInfo :: Name -> Type -> IdInfo -> Id
235 mkLocalIdWithInfo name ty info = Var.mkLocalVar VanillaId name ty info
236         -- Note [Free type variables]
237
238 -- | Create a local 'Id' that is marked as exported. 
239 -- This prevents things attached to it from being removed as dead code.
240 mkExportedLocalId :: Name -> Type -> Id
241 mkExportedLocalId name ty = Var.mkExportedLocalVar VanillaId name ty vanillaIdInfo
242         -- Note [Free type variables]
243
244
245 -- | Create a system local 'Id'. These are local 'Id's (see "Var#globalvslocal") 
246 -- that are created by the compiler out of thin air
247 mkSysLocal :: FastString -> Unique -> Type -> Id
248 mkSysLocal fs uniq ty = mkLocalId (mkSystemVarName uniq fs) ty
249
250 mkSysLocalM :: MonadUnique m => FastString -> Type -> m Id
251 mkSysLocalM fs ty = getUniqueM >>= (\uniq -> return (mkSysLocal fs uniq ty))
252
253
254 -- | Create a user local 'Id'. These are local 'Id's (see "Var#globalvslocal") with a name and location that the user might recognize
255 mkUserLocal :: OccName -> Unique -> Type -> SrcSpan -> Id
256 mkUserLocal occ uniq ty loc = mkLocalId (mkInternalName uniq occ loc) ty
257
258 mkUserLocalM :: MonadUnique m => OccName -> Type -> SrcSpan -> m Id
259 mkUserLocalM occ ty loc = getUniqueM >>= (\uniq -> return (mkUserLocal occ uniq ty loc))
260
261 \end{code}
262
263 Make some local @Ids@ for a template @CoreExpr@.  These have bogus
264 @Uniques@, but that's OK because the templates are supposed to be
265 instantiated before use.
266  
267 \begin{code}
268 -- | Workers get local names. "CoreTidy" will externalise these if necessary
269 mkWorkerId :: Unique -> Id -> Type -> Id
270 mkWorkerId uniq unwrkr ty
271   = mkLocalId (mkDerivedInternalName mkWorkerOcc uniq (getName unwrkr)) ty
272
273 -- | Create a /template local/: a family of system local 'Id's in bijection with @Int@s, typically used in unfoldings
274 mkTemplateLocal :: Int -> Type -> Id
275 mkTemplateLocal i ty = mkSysLocal (fsLit "tpl") (mkBuiltinUnique i) ty
276
277 -- | Create a template local for a series of types
278 mkTemplateLocals :: [Type] -> [Id]
279 mkTemplateLocals = mkTemplateLocalsNum 1
280
281 -- | Create a template local for a series of type, but start from a specified template local
282 mkTemplateLocalsNum :: Int -> [Type] -> [Id]
283 mkTemplateLocalsNum n tys = zipWith mkTemplateLocal [n..] tys
284 \end{code}
285
286
287 %************************************************************************
288 %*                                                                      *
289 \subsection{Special Ids}
290 %*                                                                      *
291 %************************************************************************
292
293 \begin{code}
294 -- | If the 'Id' is that for a record selector, extract the 'sel_tycon' and label. Panic otherwise
295 recordSelectorFieldLabel :: Id -> (TyCon, FieldLabel)
296 recordSelectorFieldLabel id
297   = case Var.idDetails id of
298         RecSelId { sel_tycon = tycon } -> (tycon, idName id)
299         _ -> panic "recordSelectorFieldLabel"
300
301 isRecordSelector        :: Id -> Bool
302 isNaughtyRecordSelector :: Id -> Bool
303 isPrimOpId              :: Id -> Bool
304 isFCallId               :: Id -> Bool
305 isDataConWorkId         :: Id -> Bool
306 isDFunId                :: Id -> Bool
307
308 isClassOpId_maybe       :: Id -> Maybe Class
309 isPrimOpId_maybe        :: Id -> Maybe PrimOp
310 isFCallId_maybe         :: Id -> Maybe ForeignCall
311 isDataConWorkId_maybe   :: Id -> Maybe DataCon
312
313 isRecordSelector id = case Var.idDetails id of
314                         RecSelId {}  -> True
315                         _               -> False
316
317 isNaughtyRecordSelector id = case Var.idDetails id of
318                         RecSelId { sel_naughty = n } -> n
319                         _                               -> False
320
321 isClassOpId_maybe id = case Var.idDetails id of
322                         ClassOpId cls -> Just cls
323                         _other        -> Nothing
324
325 isPrimOpId id = case Var.idDetails id of
326                         PrimOpId _ -> True
327                         _          -> False
328
329 isDFunId id = case Var.idDetails id of
330                         DFunId _ -> True
331                         _        -> False
332
333 isPrimOpId_maybe id = case Var.idDetails id of
334                         PrimOpId op -> Just op
335                         _           -> Nothing
336
337 isFCallId id = case Var.idDetails id of
338                         FCallId _ -> True
339                         _         -> False
340
341 isFCallId_maybe id = case Var.idDetails id of
342                         FCallId call -> Just call
343                         _            -> Nothing
344
345 isDataConWorkId id = case Var.idDetails id of
346                         DataConWorkId _ -> True
347                         _               -> False
348
349 isDataConWorkId_maybe id = case Var.idDetails id of
350                         DataConWorkId con -> Just con
351                         _                 -> Nothing
352
353 isDataConId_maybe :: Id -> Maybe DataCon
354 isDataConId_maybe id = case Var.idDetails id of
355                          DataConWorkId con -> Just con
356                          DataConWrapId con -> Just con
357                          _                 -> Nothing
358
359 idDataCon :: Id -> DataCon
360 -- ^ Get from either the worker or the wrapper 'Id' to the 'DataCon'. Currently used only in the desugarer.
361 --
362 -- INVARIANT: @idDataCon (dataConWrapId d) = d@: remember, 'dataConWrapId' can return either the wrapper or the worker
363 idDataCon id = isDataConId_maybe id `orElse` pprPanic "idDataCon" (ppr id)
364
365
366 isDictId :: Id -> Bool
367 isDictId id = isDictTy (idType id)
368
369 hasNoBinding :: Id -> Bool
370 -- ^ Returns @True@ of an 'Id' which may not have a
371 -- binding, even though it is defined in this module.
372
373 -- Data constructor workers used to be things of this kind, but
374 -- they aren't any more.  Instead, we inject a binding for 
375 -- them at the CorePrep stage. 
376 -- EXCEPT: unboxed tuples, which definitely have no binding
377 hasNoBinding id = case Var.idDetails id of
378                         PrimOpId _       -> True        -- See Note [Primop wrappers]
379                         FCallId _        -> True
380                         DataConWorkId dc -> isUnboxedTupleCon dc
381                         _                -> False
382
383 isImplicitId :: Id -> Bool
384 -- ^ 'isImplicitId' tells whether an 'Id's info is implied by other
385 -- declarations, so we don't need to put its signature in an interface
386 -- file, even if it's mentioned in some other interface unfolding.
387 isImplicitId id
388   = case Var.idDetails id of
389         FCallId {}       -> True
390         ClassOpId {}     -> True
391         PrimOpId {}      -> True
392         DataConWorkId {} -> True
393         DataConWrapId {} -> True
394                 -- These are are implied by their type or class decl;
395                 -- remember that all type and class decls appear in the interface file.
396                 -- The dfun id is not an implicit Id; it must *not* be omitted, because 
397                 -- it carries version info for the instance decl
398         _               -> False
399
400 idIsFrom :: Module -> Id -> Bool
401 idIsFrom mod id = nameIsLocalOrFrom mod (idName id)
402 \end{code}
403
404 Note [Primop wrappers]
405 ~~~~~~~~~~~~~~~~~~~~~~
406 Currently hasNoBinding claims that PrimOpIds don't have a curried
407 function definition.  But actually they do, in GHC.PrimopWrappers,
408 which is auto-generated from prelude/primops.txt.pp.  So actually, hasNoBinding
409 could return 'False' for PrimOpIds.
410
411 But we'd need to add something in CoreToStg to swizzle any unsaturated
412 applications of GHC.Prim.plusInt# to GHC.PrimopWrappers.plusInt#.
413
414 Nota Bene: GHC.PrimopWrappers is needed *regardless*, because it's
415 used by GHCi, which does not implement primops direct at all.
416
417
418
419 \begin{code}
420 isDeadBinder :: Id -> Bool
421 isDeadBinder bndr | isId bndr = isDeadOcc (idOccInfo bndr)
422                   | otherwise = False   -- TyVars count as not dead
423 \end{code}
424
425 \begin{code}
426 isTickBoxOp :: Id -> Bool
427 isTickBoxOp id = 
428   case Var.idDetails id of
429     TickBoxOpId _    -> True
430     _                -> False
431
432 isTickBoxOp_maybe :: Id -> Maybe TickBoxOp
433 isTickBoxOp_maybe id = 
434   case Var.idDetails id of
435     TickBoxOpId tick -> Just tick
436     _                -> Nothing
437 \end{code}
438
439 %************************************************************************
440 %*                                                                      *
441 \subsection{IdInfo stuff}
442 %*                                                                      *
443 %************************************************************************
444
445 \begin{code}
446         ---------------------------------
447         -- ARITY
448 idArity :: Id -> Arity
449 idArity id = arityInfo (idInfo id)
450
451 setIdArity :: Id -> Arity -> Id
452 setIdArity id arity = modifyIdInfo (`setArityInfo` arity) id
453
454 -- | Returns true if an application to n args would diverge
455 isBottomingId :: Id -> Bool
456 isBottomingId id = isBottomingSig (idStrictness id)
457
458 idStrictness_maybe :: Id -> Maybe StrictSig
459 idStrictness :: Id -> StrictSig
460
461 idStrictness_maybe id = strictnessInfo (idInfo id)
462 idStrictness       id = idStrictness_maybe id `orElse` topSig
463
464 setIdStrictness :: Id -> StrictSig -> Id
465 setIdStrictness id sig = modifyIdInfo (`setStrictnessInfo` Just sig) id
466
467 zapIdStrictness :: Id -> Id
468 zapIdStrictness id = modifyIdInfo (`setStrictnessInfo` Nothing) id
469
470 -- | This predicate says whether the 'Id' has a strict demand placed on it or
471 -- has a type such that it can always be evaluated strictly (e.g., an
472 -- unlifted type, but see the comment for 'isStrictType').  We need to
473 -- check separately whether the 'Id' has a so-called \"strict type\" because if
474 -- the demand for the given @id@ hasn't been computed yet but @id@ has a strict
475 -- type, we still want @isStrictId id@ to be @True@.
476 isStrictId :: Id -> Bool
477 isStrictId id
478   = ASSERT2( isId id, text "isStrictId: not an id: " <+> ppr id )
479            (isStrictDmd (idDemandInfo id)) || 
480            (isStrictType (idType id))
481
482         ---------------------------------
483         -- UNFOLDING
484 idUnfolding :: Id -> Unfolding
485 -- Do not expose the unfolding of a loop breaker!
486 idUnfolding id 
487   | isNonRuleLoopBreaker (occInfo info) = NoUnfolding
488   | otherwise                           = unfoldingInfo info
489   where
490     info = idInfo id
491
492 realIdUnfolding :: Id -> Unfolding
493 -- Expose the unfolding if there is one, including for loop breakers
494 realIdUnfolding id = unfoldingInfo (idInfo id)
495
496 setIdUnfolding :: Id -> Unfolding -> Id
497 setIdUnfolding id unfolding = modifyIdInfo (`setUnfoldingInfo` unfolding) id
498
499 idDemandInfo_maybe :: Id -> Maybe Demand
500 idDemandInfo       :: Id -> Demand
501
502 idDemandInfo_maybe id = demandInfo (idInfo id)
503 idDemandInfo       id = demandInfo (idInfo id) `orElse` topDmd
504
505 setIdDemandInfo :: Id -> Demand -> Id
506 setIdDemandInfo id dmd = modifyIdInfo (`setDemandInfo` Just dmd) id
507
508         ---------------------------------
509         -- SPECIALISATION
510
511 -- See Note [Specialisations and RULES in IdInfo] in IdInfo.lhs
512
513 idSpecialisation :: Id -> SpecInfo
514 idSpecialisation id = specInfo (idInfo id)
515
516 idCoreRules :: Id -> [CoreRule]
517 idCoreRules id = specInfoRules (idSpecialisation id)
518
519 idHasRules :: Id -> Bool
520 idHasRules id = not (isEmptySpecInfo (idSpecialisation id))
521
522 setIdSpecialisation :: Id -> SpecInfo -> Id
523 setIdSpecialisation id spec_info = modifyIdInfo (`setSpecInfo` spec_info) id
524
525         ---------------------------------
526         -- CAF INFO
527 idCafInfo :: Id -> CafInfo
528 idCafInfo id = cafInfo (idInfo id)
529
530 setIdCafInfo :: Id -> CafInfo -> Id
531 setIdCafInfo id caf_info = modifyIdInfo (`setCafInfo` caf_info) id
532
533         ---------------------------------
534         -- Occcurrence INFO
535 idOccInfo :: Id -> OccInfo
536 idOccInfo id = occInfo (idInfo id)
537
538 setIdOccInfo :: Id -> OccInfo -> Id
539 setIdOccInfo id occ_info = modifyIdInfo (`setOccInfo` occ_info) id
540
541 zapIdOccInfo :: Id -> Id
542 zapIdOccInfo b = b `setIdOccInfo` NoOccInfo
543 \end{code}
544
545
546         ---------------------------------
547         -- INLINING
548 The inline pragma tells us to be very keen to inline this Id, but it's still
549 OK not to if optimisation is switched off.
550
551 \begin{code}
552 idInlinePragma :: Id -> InlinePragma
553 idInlinePragma id = inlinePragInfo (idInfo id)
554
555 setInlinePragma :: Id -> InlinePragma -> Id
556 setInlinePragma id prag = modifyIdInfo (`setInlinePragInfo` prag) id
557
558 modifyInlinePragma :: Id -> (InlinePragma -> InlinePragma) -> Id
559 modifyInlinePragma id fn = modifyIdInfo (\info -> info `setInlinePragInfo` (fn (inlinePragInfo info))) id
560
561 idInlineActivation :: Id -> Activation
562 idInlineActivation id = inlinePragmaActivation (idInlinePragma id)
563
564 setInlineActivation :: Id -> Activation -> Id
565 setInlineActivation id act = modifyInlinePragma id (\prag -> setInlinePragmaActivation prag act)
566
567 idRuleMatchInfo :: Id -> RuleMatchInfo
568 idRuleMatchInfo id = inlinePragmaRuleMatchInfo (idInlinePragma id)
569
570 isConLikeId :: Id -> Bool
571 isConLikeId id = isDataConWorkId id || isConLike (idRuleMatchInfo id)
572 \end{code}
573
574
575         ---------------------------------
576         -- ONE-SHOT LAMBDAS
577 \begin{code}
578 idLBVarInfo :: Id -> LBVarInfo
579 idLBVarInfo id = lbvarInfo (idInfo id)
580
581 -- | Returns whether the lambda associated with the 'Id' is certainly applied at most once
582 -- OR we are applying the \"state hack\" which makes it appear as if theis is the case for
583 -- lambdas used in @IO@. You should prefer using this over 'isOneShotLambda'
584 isOneShotBndr :: Id -> Bool
585 -- This one is the "business end", called externally.
586 -- Its main purpose is to encapsulate the Horrible State Hack
587 isOneShotBndr id = isOneShotLambda id || isStateHackType (idType id)
588
589 -- | Should we apply the state hack to values of this 'Type'?
590 isStateHackType :: Type -> Bool
591 isStateHackType ty
592   | opt_NoStateHack 
593   = False
594   | otherwise
595   = case splitTyConApp_maybe ty of
596         Just (tycon,_) -> tycon == statePrimTyCon
597         _              -> False
598         -- This is a gross hack.  It claims that 
599         -- every function over realWorldStatePrimTy is a one-shot
600         -- function.  This is pretty true in practice, and makes a big
601         -- difference.  For example, consider
602         --      a `thenST` \ r -> ...E...
603         -- The early full laziness pass, if it doesn't know that r is one-shot
604         -- will pull out E (let's say it doesn't mention r) to give
605         --      let lvl = E in a `thenST` \ r -> ...lvl...
606         -- When `thenST` gets inlined, we end up with
607         --      let lvl = E in \s -> case a s of (r, s') -> ...lvl...
608         -- and we don't re-inline E.
609         --
610         -- It would be better to spot that r was one-shot to start with, but
611         -- I don't want to rely on that.
612         --
613         -- Another good example is in fill_in in PrelPack.lhs.  We should be able to
614         -- spot that fill_in has arity 2 (and when Keith is done, we will) but we can't yet.
615
616
617 -- | Returns whether the lambda associated with the 'Id' is certainly applied at most once.
618 -- You probably want to use 'isOneShotBndr' instead
619 isOneShotLambda :: Id -> Bool
620 isOneShotLambda id = case idLBVarInfo id of
621                        IsOneShotLambda  -> True
622                        NoLBVarInfo      -> False
623
624 setOneShotLambda :: Id -> Id
625 setOneShotLambda id = modifyIdInfo (`setLBVarInfo` IsOneShotLambda) id
626
627 clearOneShotLambda :: Id -> Id
628 clearOneShotLambda id 
629   | isOneShotLambda id = modifyIdInfo (`setLBVarInfo` NoLBVarInfo) id
630   | otherwise          = id                     
631
632 -- The OneShotLambda functions simply fiddle with the IdInfo flag
633 -- But watch out: this may change the type of something else
634 --      f = \x -> e
635 -- If we change the one-shot-ness of x, f's type changes
636 \end{code}
637
638 \begin{code}
639 zapInfo :: (IdInfo -> Maybe IdInfo) -> Id -> Id
640 zapInfo zapper id = maybeModifyIdInfo (zapper (idInfo id)) id
641
642 zapLamIdInfo :: Id -> Id
643 zapLamIdInfo = zapInfo zapLamInfo
644
645 zapDemandIdInfo :: Id -> Id
646 zapDemandIdInfo = zapInfo zapDemandInfo
647
648 zapFragileIdInfo :: Id -> Id
649 zapFragileIdInfo = zapInfo zapFragileInfo 
650 \end{code}
651
652 Note [transferPolyIdInfo]
653 ~~~~~~~~~~~~~~~~~~~~~~~~~
654 Suppose we have
655
656    f = /\a. let g = rhs in ...
657
658 where g has interesting strictness information.  Then if we float thus
659
660    g' = /\a. rhs
661    f = /\a. ...[g' a/g]
662
663 we *do not* want to lose g's
664   * strictness information
665   * arity 
666   * inline pragma (though that is bit more debatable)
667
668 It's simple to retain strictness and arity, but not so simple to retain
669   * worker info
670   * rules
671 so we simply discard those.  Sooner or later this may bite us.
672
673 This transfer is used in two places: 
674         FloatOut (long-distance let-floating)
675         SimplUtils.abstractFloats (short-distance let-floating)
676
677 If we abstract wrt one or more *value* binders, we must modify the 
678 arity and strictness info before transferring it.  E.g. 
679       f = \x. e
680 -->
681       g' = \y. \x. e
682       + substitute (g' y) for g
683 Notice that g' has an arity one more than the original g
684
685 \begin{code}
686 transferPolyIdInfo :: Id        -- Original Id
687                    -> [Var]     -- Abstract wrt these variables
688                    -> Id        -- New Id
689                    -> Id
690 transferPolyIdInfo old_id abstract_wrt new_id
691   = modifyIdInfo transfer new_id
692   where
693     arity_increase = count isId abstract_wrt    -- Arity increases by the
694                                                 -- number of value binders
695
696     old_info        = idInfo old_id
697     old_arity       = arityInfo old_info
698     old_inline_prag = inlinePragInfo old_info
699     new_arity       = old_arity + arity_increase
700     old_strictness  = strictnessInfo old_info
701     new_strictness  = fmap (increaseStrictSigArity arity_increase) old_strictness
702
703     transfer new_info = new_info `setStrictnessInfo` new_strictness
704                                  `setArityInfo` new_arity
705                                  `setInlinePragInfo` old_inline_prag
706 \end{code}