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