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