[project @ 2005-04-04 11:55:11 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / IdInfo.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
3 %
4 \section[IdInfo]{@IdInfos@: Non-essential information about @Ids@}
5
6 (And a pretty good illustration of quite a few things wrong with
7 Haskell. [WDP 94/11])
8
9 \begin{code}
10 module IdInfo (
11         GlobalIdDetails(..), notGlobalId,       -- Not abstract
12
13         IdInfo,         -- Abstract
14         vanillaIdInfo, noCafIdInfo,
15         seqIdInfo, megaSeqIdInfo,
16
17         -- Zapping
18         zapLamInfo, zapDemandInfo,
19
20         -- Arity
21         ArityInfo,
22         unknownArity, 
23         arityInfo, setArityInfo, ppArityInfo, 
24
25         -- New demand and strictness info
26         newStrictnessInfo, setNewStrictnessInfo, 
27         newDemandInfo, setNewDemandInfo, pprNewStrictness,
28         setAllStrictnessInfo,
29
30 #ifdef OLD_STRICTNESS
31         -- Strictness; imported from Demand
32         StrictnessInfo(..),
33         mkStrictnessInfo, noStrictnessInfo,
34         ppStrictnessInfo,isBottomingStrictness, 
35 #endif
36
37         -- Worker
38         WorkerInfo(..), workerExists, wrapperArity, workerId,
39         workerInfo, setWorkerInfo, ppWorkerInfo,
40
41         -- Unfolding
42         unfoldingInfo, setUnfoldingInfo, setUnfoldingInfoLazily,
43
44 #ifdef OLD_STRICTNESS
45         -- Old DemandInfo and StrictnessInfo
46         demandInfo, setDemandInfo, 
47         strictnessInfo, setStrictnessInfo,
48         cprInfoFromNewStrictness,
49         oldStrictnessFromNew, newStrictnessFromOld,
50         oldDemand, newDemand,
51
52         -- Constructed Product Result Info
53         CprInfo(..), cprInfo, setCprInfo, ppCprInfo, noCprInfo,
54 #endif
55
56         -- Inline prags
57         InlinePragInfo, 
58         inlinePragInfo, setInlinePragInfo, 
59
60         -- Occurrence info
61         OccInfo(..), isFragileOcc, isDeadOcc, isLoopBreaker,
62         InsideLam, OneBranch, insideLam, notInsideLam, oneBranch, notOneBranch,
63         occInfo, setOccInfo, 
64
65         -- Specialisation
66         specInfo, setSpecInfo,
67
68         -- CAF info
69         CafInfo(..), cafInfo, ppCafInfo, setCafInfo, mayHaveCafRefs,
70
71         -- Lambda-bound variable info
72         LBVarInfo(..), lbvarInfo, setLBVarInfo, noLBVarInfo, hasNoLBVarInfo
73     ) where
74
75 #include "HsVersions.h"
76
77
78 import CoreSyn
79 import Class            ( Class )
80 import PrimOp           ( PrimOp )
81 import Var              ( Id )
82 import BasicTypes       ( OccInfo(..), isFragileOcc, isDeadOcc, seqOccInfo, isLoopBreaker,
83                           InsideLam, insideLam, notInsideLam, 
84                           OneBranch, oneBranch, notOneBranch,
85                           Arity,
86                           Activation(..)
87                         )
88 import DataCon          ( DataCon )
89 import TyCon            ( TyCon, FieldLabel )
90 import ForeignCall      ( ForeignCall )
91 import NewDemand
92 import Outputable       
93 import Maybe            ( isJust )
94
95 #ifdef OLD_STRICTNESS
96 import Name             ( Name )
97 import Demand           hiding( Demand, seqDemand )
98 import qualified Demand
99 import Util             ( listLengthCmp )
100 import List             ( replicate )
101 #endif
102
103 -- infixl so you can say (id `set` a `set` b)
104 infixl  1 `setSpecInfo`,
105           `setArityInfo`,
106           `setInlinePragInfo`,
107           `setUnfoldingInfo`,
108           `setWorkerInfo`,
109           `setLBVarInfo`,
110           `setOccInfo`,
111           `setCafInfo`,
112           `setNewStrictnessInfo`,
113           `setAllStrictnessInfo`,
114           `setNewDemandInfo`
115 #ifdef OLD_STRICTNESS
116           , `setCprInfo`
117           , `setDemandInfo`
118           , `setStrictnessInfo`
119 #endif
120 \end{code}
121
122 %************************************************************************
123 %*                                                                      *
124 \subsection{New strictness info}
125 %*                                                                      *
126 %************************************************************************
127
128 To be removed later
129
130 \begin{code}
131 -- setAllStrictnessInfo :: IdInfo -> Maybe StrictSig -> IdInfo
132 -- Set old and new strictness info
133 setAllStrictnessInfo info Nothing
134   = info { newStrictnessInfo = Nothing
135 #ifdef OLD_STRICTNESS
136          , strictnessInfo = NoStrictnessInfo
137          , cprInfo = NoCPRInfo
138 #endif
139          }
140
141 setAllStrictnessInfo info (Just sig)
142   = info { newStrictnessInfo = Just sig
143 #ifdef OLD_STRICTNESS
144          , strictnessInfo = oldStrictnessFromNew sig
145          , cprInfo = cprInfoFromNewStrictness sig
146 #endif
147          }
148
149 seqNewStrictnessInfo Nothing = ()
150 seqNewStrictnessInfo (Just ty) = seqStrictSig ty
151
152 pprNewStrictness Nothing = empty
153 pprNewStrictness (Just sig) = ftext FSLIT("Str:") <+> ppr sig
154
155 #ifdef OLD_STRICTNESS
156 oldStrictnessFromNew :: StrictSig -> Demand.StrictnessInfo
157 oldStrictnessFromNew sig = mkStrictnessInfo (map oldDemand dmds, isBotRes res_info)
158                          where
159                            (dmds, res_info) = splitStrictSig sig
160
161 cprInfoFromNewStrictness :: StrictSig -> CprInfo
162 cprInfoFromNewStrictness sig = case strictSigResInfo sig of
163                                   RetCPR -> ReturnsCPR
164                                   other  -> NoCPRInfo
165
166 newStrictnessFromOld :: Name -> Arity -> Demand.StrictnessInfo -> CprInfo -> StrictSig
167 newStrictnessFromOld name arity (Demand.StrictnessInfo ds res) cpr
168   | listLengthCmp ds arity /= GT -- length ds <= arity
169         -- Sometimes the old strictness analyser has more
170         -- demands than the arity justifies
171   = mk_strict_sig name arity $
172     mkTopDmdType (map newDemand ds) (newRes res cpr)
173
174 newStrictnessFromOld name arity other cpr
175   =     -- Either no strictness info, or arity is too small
176         -- In either case we can't say anything useful
177     mk_strict_sig name arity $
178     mkTopDmdType (replicate arity lazyDmd) (newRes False cpr)
179
180 mk_strict_sig name arity dmd_ty
181   = WARN( arity /= dmdTypeDepth dmd_ty, ppr name <+> (ppr arity $$ ppr dmd_ty) )
182     mkStrictSig dmd_ty
183
184 newRes True  _          = BotRes
185 newRes False ReturnsCPR = retCPR
186 newRes False NoCPRInfo  = TopRes
187
188 newDemand :: Demand.Demand -> NewDemand.Demand
189 newDemand (WwLazy True)      = Abs
190 newDemand (WwLazy False)     = lazyDmd
191 newDemand WwStrict           = evalDmd
192 newDemand (WwUnpack unpk ds) = Eval (Prod (map newDemand ds))
193 newDemand WwPrim             = lazyDmd
194 newDemand WwEnum             = evalDmd
195
196 oldDemand :: NewDemand.Demand -> Demand.Demand
197 oldDemand Abs              = WwLazy True
198 oldDemand Top              = WwLazy False
199 oldDemand Bot              = WwStrict
200 oldDemand (Box Bot)        = WwStrict
201 oldDemand (Box Abs)        = WwLazy False
202 oldDemand (Box (Eval _))   = WwStrict   -- Pass box only
203 oldDemand (Defer d)        = WwLazy False
204 oldDemand (Eval (Prod ds)) = WwUnpack True (map oldDemand ds)
205 oldDemand (Eval (Poly _))  = WwStrict
206 oldDemand (Call _)         = WwStrict
207
208 #endif /* OLD_STRICTNESS */
209 \end{code}
210
211
212 \begin{code}
213 seqNewDemandInfo Nothing    = ()
214 seqNewDemandInfo (Just dmd) = seqDemand dmd
215 \end{code}
216
217
218 %************************************************************************
219 %*                                                                      *
220 \subsection{GlobalIdDetails
221 %*                                                                      *
222 %************************************************************************
223
224 This type is here (rather than in Id.lhs) mainly because there's 
225 an IdInfo.hi-boot, but no Id.hi-boot, and GlobalIdDetails is imported
226 (recursively) by Var.lhs.
227
228 \begin{code}
229 data GlobalIdDetails
230   = VanillaGlobal               -- Imported from elsewhere, a default method Id.
231
232   | RecordSelId TyCon FieldLabel  -- The Id for a record selector
233
234   | DataConWorkId DataCon       -- The Id for a data constructor *worker*
235   | DataConWrapId DataCon       -- The Id for a data constructor *wrapper*
236                                 -- [the only reasons we need to know is so that
237                                 --  a) we can  suppress printing a definition in the interface file
238                                 --  b) when typechecking a pattern we can get from the
239                                 --     Id back to the data con]
240
241   | ClassOpId Class             -- An operation of a class
242
243   | PrimOpId PrimOp             -- The Id for a primitive operator
244   | FCallId ForeignCall         -- The Id for a foreign call
245
246   | NotGlobalId                 -- Used as a convenient extra return value from globalIdDetails
247     
248 notGlobalId = NotGlobalId
249
250 instance Outputable GlobalIdDetails where
251     ppr NotGlobalId       = ptext SLIT("[***NotGlobalId***]")
252     ppr VanillaGlobal     = ptext SLIT("[GlobalId]")
253     ppr (DataConWorkId _) = ptext SLIT("[DataCon]")
254     ppr (DataConWrapId _) = ptext SLIT("[DataConWrapper]")
255     ppr (ClassOpId _)     = ptext SLIT("[ClassOp]")
256     ppr (PrimOpId _)      = ptext SLIT("[PrimOp]")
257     ppr (FCallId _)       = ptext SLIT("[ForeignCall]")
258     ppr (RecordSelId _ _) = ptext SLIT("[RecSel]")
259 \end{code}
260
261
262 %************************************************************************
263 %*                                                                      *
264 \subsection{The main IdInfo type}
265 %*                                                                      *
266 %************************************************************************
267
268 An @IdInfo@ gives {\em optional} information about an @Id@.  If
269 present it never lies, but it may not be present, in which case there
270 is always a conservative assumption which can be made.
271
272 Two @Id@s may have different info even though they have the same
273 @Unique@ (and are hence the same @Id@); for example, one might lack
274 the properties attached to the other.
275
276 The @IdInfo@ gives information about the value, or definition, of the
277 @Id@.  It does {\em not} contain information about the @Id@'s usage
278 (except for @DemandInfo@? ToDo). (@lbvarInfo@ is also a marginal
279 case.  KSW 1999-04).
280
281 \begin{code}
282 data IdInfo
283   = IdInfo {
284         arityInfo       :: !ArityInfo,          -- Its arity
285         specInfo        :: CoreRules,           -- Specialisations of this function which exist
286 #ifdef OLD_STRICTNESS
287         cprInfo         :: CprInfo,             -- Function always constructs a product result
288         demandInfo      :: Demand.Demand,       -- Whether or not it is definitely demanded
289         strictnessInfo  :: StrictnessInfo,      -- Strictness properties
290 #endif
291         workerInfo      :: WorkerInfo,          -- Pointer to Worker Function
292                                                 -- Within one module this is irrelevant; the 
293                                                 -- inlining of a worker is handled via the Unfolding
294                                                 -- WorkerInfo is used *only* to indicate the form of
295                                                 -- the RHS, so that interface files don't actually 
296                                                 -- need to contain the RHS; it can be derived from
297                                                 -- the strictness info
298
299         unfoldingInfo   :: Unfolding,           -- Its unfolding
300         cafInfo         :: CafInfo,             -- CAF info
301         lbvarInfo       :: LBVarInfo,           -- Info about a lambda-bound variable
302         inlinePragInfo  :: InlinePragInfo,      -- Inline pragma
303         occInfo         :: OccInfo,             -- How it occurs
304
305         newStrictnessInfo :: Maybe StrictSig,   -- Reason for Maybe: the DmdAnal phase needs to
306                                                 -- know whether whether this is the first visit,
307                                                 -- so it can assign botSig.  Other customers want
308                                                 -- topSig.  So Nothing is good.
309
310         newDemandInfo     :: Maybe Demand       -- Similarly we want to know if there's no
311                                                 -- known demand yet, for when we are looking for
312                                                 -- CPR info
313     }
314
315 seqIdInfo :: IdInfo -> ()
316 seqIdInfo (IdInfo {}) = ()
317
318 megaSeqIdInfo :: IdInfo -> ()
319 megaSeqIdInfo info
320   = seqRules (specInfo info)                    `seq`
321     seqWorker (workerInfo info)                 `seq`
322
323 -- Omitting this improves runtimes a little, presumably because
324 -- some unfoldings are not calculated at all
325 --    seqUnfolding (unfoldingInfo info)         `seq`
326
327     seqNewDemandInfo (newDemandInfo info)       `seq`
328     seqNewStrictnessInfo (newStrictnessInfo info) `seq`
329
330 #ifdef OLD_STRICTNESS
331     Demand.seqDemand (demandInfo info)          `seq`
332     seqStrictnessInfo (strictnessInfo info)     `seq`
333     seqCpr (cprInfo info)                       `seq`
334 #endif
335
336     seqCaf (cafInfo info)                       `seq`
337     seqLBVar (lbvarInfo info)                   `seq`
338     seqOccInfo (occInfo info) 
339 \end{code}
340
341 Setters
342
343 \begin{code}
344 setWorkerInfo     info wk = wk `seq` info { workerInfo = wk }
345 setSpecInfo       info sp = sp `seq` info { specInfo = sp }
346 setInlinePragInfo info pr = pr `seq` info { inlinePragInfo = pr }
347 setOccInfo        info oc = oc `seq` info { occInfo = oc }
348 #ifdef OLD_STRICTNESS
349 setStrictnessInfo info st = st `seq` info { strictnessInfo = st }
350 #endif
351         -- Try to avoid spack leaks by seq'ing
352
353 setUnfoldingInfoLazily info uf  -- Lazy variant to avoid looking at the
354   =                             -- unfolding of an imported Id unless necessary
355     info { unfoldingInfo = uf } -- (In this case the demand-zapping is redundant.)
356
357 setUnfoldingInfo info uf 
358         -- We do *not* seq on the unfolding info, For some reason, doing so 
359         -- actually increases residency significantly. 
360   = info { unfoldingInfo = uf }
361
362 #ifdef OLD_STRICTNESS
363 setDemandInfo     info dd = info { demandInfo = dd }
364 setCprInfo        info cp = info { cprInfo = cp }
365 #endif
366
367 setArityInfo      info ar  = info { arityInfo = ar  }
368 setCafInfo        info caf = info { cafInfo = caf }
369
370 setLBVarInfo      info lb = {-lb `seq`-} info { lbvarInfo = lb }
371
372 setNewDemandInfo     info dd = dd `seq` info { newDemandInfo = dd }
373 setNewStrictnessInfo info dd = dd `seq` info { newStrictnessInfo = dd }
374 \end{code}
375
376
377 \begin{code}
378 vanillaIdInfo :: IdInfo
379 vanillaIdInfo 
380   = IdInfo {
381             cafInfo             = vanillaCafInfo,
382             arityInfo           = unknownArity,
383 #ifdef OLD_STRICTNESS
384             cprInfo             = NoCPRInfo,
385             demandInfo          = wwLazy,
386             strictnessInfo      = NoStrictnessInfo,
387 #endif
388             specInfo            = emptyCoreRules,
389             workerInfo          = NoWorker,
390             unfoldingInfo       = noUnfolding,
391             lbvarInfo           = NoLBVarInfo,
392             inlinePragInfo      = AlwaysActive,
393             occInfo             = NoOccInfo,
394             newDemandInfo       = Nothing,
395             newStrictnessInfo   = Nothing
396            }
397
398 noCafIdInfo  = vanillaIdInfo `setCafInfo`    NoCafRefs
399         -- Used for built-in type Ids in MkId.
400 \end{code}
401
402
403 %************************************************************************
404 %*                                                                      *
405 \subsection[arity-IdInfo]{Arity info about an @Id@}
406 %*                                                                      *
407 %************************************************************************
408
409 For locally-defined Ids, the code generator maintains its own notion
410 of their arities; so it should not be asking...  (but other things
411 besides the code-generator need arity info!)
412
413 \begin{code}
414 type ArityInfo = Arity
415         -- A partial application of this Id to up to n-1 value arguments
416         -- does essentially no work.  That is not necessarily the
417         -- same as saying that it has n leading lambdas, because coerces
418         -- may get in the way.
419
420         -- The arity might increase later in the compilation process, if
421         -- an extra lambda floats up to the binding site.
422
423 unknownArity = 0 :: Arity
424
425 ppArityInfo 0 = empty
426 ppArityInfo n = hsep [ptext SLIT("Arity"), int n]
427 \end{code}
428
429 %************************************************************************
430 %*                                                                      *
431 \subsection{Inline-pragma information}
432 %*                                                                      *
433 %************************************************************************
434
435 \begin{code}
436 type InlinePragInfo = Activation
437         -- Tells when the inlining is active
438         -- When it is active the thing may be inlined, depending on how
439         -- big it is.
440         --
441         -- If there was an INLINE pragma, then as a separate matter, the
442         -- RHS will have been made to look small with a CoreSyn Inline Note
443 \end{code}
444
445
446 %************************************************************************
447 %*                                                                      *
448 \subsection[worker-IdInfo]{Worker info about an @Id@}
449 %*                                                                      *
450 %************************************************************************
451
452 If this Id has a worker then we store a reference to it. Worker
453 functions are generated by the worker/wrapper pass.  This uses
454 information from strictness analysis.
455
456 There might not be a worker, even for a strict function, because:
457 (a) the function might be small enough to inline, so no need 
458     for w/w split
459 (b) the strictness info might be "SSS" or something, so no w/w split.
460
461 Sometimes the arity of a wrapper changes from the original arity from
462 which it was generated, so we always emit the "original" arity into
463 the interface file, as part of the worker info.
464
465 How can this happen?  Sometimes we get
466         f = coerce t (\x y -> $wf x y)
467 at the moment of w/w split; but the eta reducer turns it into
468         f = coerce t $wf
469 which is perfectly fine except that the exposed arity so far as
470 the code generator is concerned (zero) differs from the arity
471 when we did the split (2).  
472
473 All this arises because we use 'arity' to mean "exactly how many
474 top level lambdas are there" in interface files; but during the
475 compilation of this module it means "how many things can I apply
476 this to".
477
478 \begin{code}
479
480 data WorkerInfo = NoWorker
481                 | HasWorker Id Arity
482         -- The Arity is the arity of the *wrapper* at the moment of the
483         -- w/w split.  See notes above.
484
485 seqWorker :: WorkerInfo -> ()
486 seqWorker (HasWorker id a) = id `seq` a `seq` ()
487 seqWorker NoWorker         = ()
488
489 ppWorkerInfo NoWorker            = empty
490 ppWorkerInfo (HasWorker wk_id _) = ptext SLIT("Worker") <+> ppr wk_id
491
492 workerExists :: WorkerInfo -> Bool
493 workerExists NoWorker        = False
494 workerExists (HasWorker _ _) = True
495
496 workerId :: WorkerInfo -> Id
497 workerId (HasWorker id _) = id
498
499 wrapperArity :: WorkerInfo -> Arity
500 wrapperArity (HasWorker _ a) = a
501 \end{code}
502
503
504 %************************************************************************
505 %*                                                                      *
506 \subsection[CG-IdInfo]{Code generator-related information}
507 %*                                                                      *
508 %************************************************************************
509
510 \begin{code}
511 -- CafInfo is used to build Static Reference Tables (see simplStg/SRT.lhs).
512
513 data CafInfo 
514         = MayHaveCafRefs                -- either:
515                                         -- (1) A function or static constructor
516                                         --     that refers to one or more CAFs,
517                                         -- (2) A real live CAF
518
519         | NoCafRefs                     -- A function or static constructor
520                                         -- that refers to no CAFs.
521
522 vanillaCafInfo = MayHaveCafRefs         -- Definitely safe
523
524 mayHaveCafRefs  MayHaveCafRefs = True
525 mayHaveCafRefs _               = False
526
527 seqCaf c = c `seq` ()
528
529 ppCafInfo NoCafRefs = ptext SLIT("NoCafRefs")
530 ppCafInfo MayHaveCafRefs = empty
531 \end{code}
532
533 %************************************************************************
534 %*                                                                      *
535 \subsection[cpr-IdInfo]{Constructed Product Result info about an @Id@}
536 %*                                                                      *
537 %************************************************************************
538
539 If the @Id@ is a function then it may have CPR info. A CPR analysis
540 phase detects whether:
541
542 \begin{enumerate}
543 \item
544 The function's return value has a product type, i.e. an algebraic  type 
545 with a single constructor. Examples of such types are tuples and boxed
546 primitive values.
547 \item
548 The function always 'constructs' the value that it is returning.  It
549 must do this on every path through,  and it's OK if it calls another
550 function which constructs the result.
551 \end{enumerate}
552
553 If this is the case then we store a template which tells us the
554 function has the CPR property and which components of the result are
555 also CPRs.   
556
557 \begin{code}
558 #ifdef OLD_STRICTNESS
559 data CprInfo
560   = NoCPRInfo
561   | ReturnsCPR  -- Yes, this function returns a constructed product
562                 -- Implicitly, this means "after the function has been applied
563                 -- to all its arguments", so the worker/wrapper builder in 
564                 -- WwLib.mkWWcpr checks that that it is indeed saturated before
565                 -- making use of the CPR info
566
567         -- We used to keep nested info about sub-components, but
568         -- we never used it so I threw it away
569
570 seqCpr :: CprInfo -> ()
571 seqCpr ReturnsCPR = ()
572 seqCpr NoCPRInfo  = ()
573
574 noCprInfo       = NoCPRInfo
575
576 ppCprInfo NoCPRInfo  = empty
577 ppCprInfo ReturnsCPR = ptext SLIT("__M")
578
579 instance Outputable CprInfo where
580     ppr = ppCprInfo
581
582 instance Show CprInfo where
583     showsPrec p c = showsPrecSDoc p (ppr c)
584 #endif
585 \end{code}
586
587
588 %************************************************************************
589 %*                                                                      *
590 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
591 %*                                                                      *
592 %************************************************************************
593
594 If the @Id@ is a lambda-bound variable then it may have lambda-bound
595 var info.  Sometimes we know whether the lambda binding this var is a
596 ``one-shot'' lambda; that is, whether it is applied at most once.
597
598 This information may be useful in optimisation, as computations may
599 safely be floated inside such a lambda without risk of duplicating
600 work.
601
602 \begin{code}
603 data LBVarInfo = NoLBVarInfo 
604                | IsOneShotLambda        -- The lambda is applied at most once).
605
606 seqLBVar l = l `seq` ()
607 \end{code}
608
609 \begin{code}
610 hasNoLBVarInfo NoLBVarInfo     = True
611 hasNoLBVarInfo IsOneShotLambda = False
612
613 noLBVarInfo = NoLBVarInfo
614
615 pprLBVarInfo NoLBVarInfo     = empty
616 pprLBVarInfo IsOneShotLambda = ptext SLIT("OneShot")
617
618 instance Outputable LBVarInfo where
619     ppr = pprLBVarInfo
620
621 instance Show LBVarInfo where
622     showsPrec p c = showsPrecSDoc p (ppr c)
623 \end{code}
624
625
626 %************************************************************************
627 %*                                                                      *
628 \subsection{Bulk operations on IdInfo}
629 %*                                                                      *
630 %************************************************************************
631
632 @zapLamInfo@ is used for lambda binders that turn out to to be
633 part of an unsaturated lambda
634
635 \begin{code}
636 zapLamInfo :: IdInfo -> Maybe IdInfo
637 zapLamInfo info@(IdInfo {occInfo = occ, newDemandInfo = demand})
638   | is_safe_occ occ && is_safe_dmd demand
639   = Nothing
640   | otherwise
641   = Just (info {occInfo = safe_occ, newDemandInfo = Nothing})
642   where
643         -- The "unsafe" occ info is the ones that say I'm not in a lambda
644         -- because that might not be true for an unsaturated lambda
645     is_safe_occ (OneOcc in_lam once) = in_lam
646     is_safe_occ other                = True
647
648     safe_occ = case occ of
649                  OneOcc _ once -> OneOcc insideLam once
650                  other         -> occ
651
652     is_safe_dmd Nothing    = True
653     is_safe_dmd (Just dmd) = not (isStrictDmd dmd)
654 \end{code}
655
656 \begin{code}
657 zapDemandInfo :: IdInfo -> Maybe IdInfo
658 zapDemandInfo info@(IdInfo {newDemandInfo = dmd})
659   | isJust dmd = Just (info {newDemandInfo = Nothing})
660   | otherwise  = Nothing
661 \end{code}
662