[project @ 2005-03-07 16:46:08 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         unfoldingInfo   :: Unfolding,           -- Its unfolding
293         cafInfo         :: CafInfo,             -- CAF info
294         lbvarInfo       :: LBVarInfo,           -- Info about a lambda-bound variable
295         inlinePragInfo  :: InlinePragInfo,      -- Inline pragma
296         occInfo         :: OccInfo,             -- How it occurs
297
298         newStrictnessInfo :: Maybe StrictSig,   -- Reason for Maybe: the DmdAnal phase needs to
299                                                 -- know whether whether this is the first visit,
300                                                 -- so it can assign botSig.  Other customers want
301                                                 -- topSig.  So Nothing is good.
302
303         newDemandInfo     :: Maybe Demand       -- Similarly we want to know if there's no
304                                                 -- known demand yet, for when we are looking for
305                                                 -- CPR info
306     }
307
308 seqIdInfo :: IdInfo -> ()
309 seqIdInfo (IdInfo {}) = ()
310
311 megaSeqIdInfo :: IdInfo -> ()
312 megaSeqIdInfo info
313   = seqRules (specInfo info)                    `seq`
314     seqWorker (workerInfo info)                 `seq`
315
316 -- Omitting this improves runtimes a little, presumably because
317 -- some unfoldings are not calculated at all
318 --    seqUnfolding (unfoldingInfo info)         `seq`
319
320     seqNewDemandInfo (newDemandInfo info)       `seq`
321     seqNewStrictnessInfo (newStrictnessInfo info) `seq`
322
323 #ifdef OLD_STRICTNESS
324     Demand.seqDemand (demandInfo info)          `seq`
325     seqStrictnessInfo (strictnessInfo info)     `seq`
326     seqCpr (cprInfo info)                       `seq`
327 #endif
328
329     seqCaf (cafInfo info)                       `seq`
330     seqLBVar (lbvarInfo info)                   `seq`
331     seqOccInfo (occInfo info) 
332 \end{code}
333
334 Setters
335
336 \begin{code}
337 setWorkerInfo     info wk = wk `seq` info { workerInfo = wk }
338 setSpecInfo       info sp = sp `seq` info { specInfo = sp }
339 setInlinePragInfo info pr = pr `seq` info { inlinePragInfo = pr }
340 setOccInfo        info oc = oc `seq` info { occInfo = oc }
341 #ifdef OLD_STRICTNESS
342 setStrictnessInfo info st = st `seq` info { strictnessInfo = st }
343 #endif
344         -- Try to avoid spack leaks by seq'ing
345
346 setUnfoldingInfoLazily info uf  -- Lazy variant to avoid looking at the
347   =                             -- unfolding of an imported Id unless necessary
348     info { unfoldingInfo = uf } -- (In this case the demand-zapping is redundant.)
349
350 setUnfoldingInfo info uf 
351         -- We do *not* seq on the unfolding info, For some reason, doing so 
352         -- actually increases residency significantly. 
353   = info { unfoldingInfo = uf }
354
355 #ifdef OLD_STRICTNESS
356 setDemandInfo     info dd = info { demandInfo = dd }
357 setCprInfo        info cp = info { cprInfo = cp }
358 #endif
359
360 setArityInfo      info ar  = info { arityInfo = ar  }
361 setCafInfo        info caf = info { cafInfo = caf }
362
363 setLBVarInfo      info lb = {-lb `seq`-} info { lbvarInfo = lb }
364
365 setNewDemandInfo     info dd = dd `seq` info { newDemandInfo = dd }
366 setNewStrictnessInfo info dd = dd `seq` info { newStrictnessInfo = dd }
367 \end{code}
368
369
370 \begin{code}
371 vanillaIdInfo :: IdInfo
372 vanillaIdInfo 
373   = IdInfo {
374             cafInfo             = vanillaCafInfo,
375             arityInfo           = unknownArity,
376 #ifdef OLD_STRICTNESS
377             cprInfo             = NoCPRInfo,
378             demandInfo          = wwLazy,
379             strictnessInfo      = NoStrictnessInfo,
380 #endif
381             specInfo            = emptyCoreRules,
382             workerInfo          = NoWorker,
383             unfoldingInfo       = noUnfolding,
384             lbvarInfo           = NoLBVarInfo,
385             inlinePragInfo      = AlwaysActive,
386             occInfo             = NoOccInfo,
387             newDemandInfo       = Nothing,
388             newStrictnessInfo   = Nothing
389            }
390
391 noCafIdInfo  = vanillaIdInfo `setCafInfo`    NoCafRefs
392         -- Used for built-in type Ids in MkId.
393 \end{code}
394
395
396 %************************************************************************
397 %*                                                                      *
398 \subsection[arity-IdInfo]{Arity info about an @Id@}
399 %*                                                                      *
400 %************************************************************************
401
402 For locally-defined Ids, the code generator maintains its own notion
403 of their arities; so it should not be asking...  (but other things
404 besides the code-generator need arity info!)
405
406 \begin{code}
407 type ArityInfo = Arity
408         -- A partial application of this Id to up to n-1 value arguments
409         -- does essentially no work.  That is not necessarily the
410         -- same as saying that it has n leading lambdas, because coerces
411         -- may get in the way.
412
413         -- The arity might increase later in the compilation process, if
414         -- an extra lambda floats up to the binding site.
415
416 unknownArity = 0 :: Arity
417
418 ppArityInfo 0 = empty
419 ppArityInfo n = hsep [ptext SLIT("Arity"), int n]
420 \end{code}
421
422 %************************************************************************
423 %*                                                                      *
424 \subsection{Inline-pragma information}
425 %*                                                                      *
426 %************************************************************************
427
428 \begin{code}
429 type InlinePragInfo = Activation
430         -- Tells when the inlining is active
431         -- When it is active the thing may be inlined, depending on how
432         -- big it is.
433         --
434         -- If there was an INLINE pragma, then as a separate matter, the
435         -- RHS will have been made to look small with a CoreSyn Inline Note
436 \end{code}
437
438
439 %************************************************************************
440 %*                                                                      *
441 \subsection[worker-IdInfo]{Worker info about an @Id@}
442 %*                                                                      *
443 %************************************************************************
444
445 If this Id has a worker then we store a reference to it. Worker
446 functions are generated by the worker/wrapper pass.  This uses
447 information from strictness analysis.
448
449 There might not be a worker, even for a strict function, because:
450 (a) the function might be small enough to inline, so no need 
451     for w/w split
452 (b) the strictness info might be "SSS" or something, so no w/w split.
453
454 Sometimes the arity of a wrapper changes from the original arity from
455 which it was generated, so we always emit the "original" arity into
456 the interface file, as part of the worker info.
457
458 How can this happen?  Sometimes we get
459         f = coerce t (\x y -> $wf x y)
460 at the moment of w/w split; but the eta reducer turns it into
461         f = coerce t $wf
462 which is perfectly fine except that the exposed arity so far as
463 the code generator is concerned (zero) differs from the arity
464 when we did the split (2).  
465
466 All this arises because we use 'arity' to mean "exactly how many
467 top level lambdas are there" in interface files; but during the
468 compilation of this module it means "how many things can I apply
469 this to".
470
471 \begin{code}
472
473 data WorkerInfo = NoWorker
474                 | HasWorker Id Arity
475         -- The Arity is the arity of the *wrapper* at the moment of the
476         -- w/w split.  See notes above.
477
478 seqWorker :: WorkerInfo -> ()
479 seqWorker (HasWorker id a) = id `seq` a `seq` ()
480 seqWorker NoWorker         = ()
481
482 ppWorkerInfo NoWorker            = empty
483 ppWorkerInfo (HasWorker wk_id _) = ptext SLIT("Worker") <+> ppr wk_id
484
485 workerExists :: WorkerInfo -> Bool
486 workerExists NoWorker        = False
487 workerExists (HasWorker _ _) = True
488
489 workerId :: WorkerInfo -> Id
490 workerId (HasWorker id _) = id
491
492 wrapperArity :: WorkerInfo -> Arity
493 wrapperArity (HasWorker _ a) = a
494 \end{code}
495
496
497 %************************************************************************
498 %*                                                                      *
499 \subsection[CG-IdInfo]{Code generator-related information}
500 %*                                                                      *
501 %************************************************************************
502
503 \begin{code}
504 -- CafInfo is used to build Static Reference Tables (see simplStg/SRT.lhs).
505
506 data CafInfo 
507         = MayHaveCafRefs                -- either:
508                                         -- (1) A function or static constructor
509                                         --     that refers to one or more CAFs,
510                                         -- (2) A real live CAF
511
512         | NoCafRefs                     -- A function or static constructor
513                                         -- that refers to no CAFs.
514
515 vanillaCafInfo = MayHaveCafRefs         -- Definitely safe
516
517 mayHaveCafRefs  MayHaveCafRefs = True
518 mayHaveCafRefs _               = False
519
520 seqCaf c = c `seq` ()
521
522 ppCafInfo NoCafRefs = ptext SLIT("NoCafRefs")
523 ppCafInfo MayHaveCafRefs = empty
524 \end{code}
525
526 %************************************************************************
527 %*                                                                      *
528 \subsection[cpr-IdInfo]{Constructed Product Result info about an @Id@}
529 %*                                                                      *
530 %************************************************************************
531
532 If the @Id@ is a function then it may have CPR info. A CPR analysis
533 phase detects whether:
534
535 \begin{enumerate}
536 \item
537 The function's return value has a product type, i.e. an algebraic  type 
538 with a single constructor. Examples of such types are tuples and boxed
539 primitive values.
540 \item
541 The function always 'constructs' the value that it is returning.  It
542 must do this on every path through,  and it's OK if it calls another
543 function which constructs the result.
544 \end{enumerate}
545
546 If this is the case then we store a template which tells us the
547 function has the CPR property and which components of the result are
548 also CPRs.   
549
550 \begin{code}
551 #ifdef OLD_STRICTNESS
552 data CprInfo
553   = NoCPRInfo
554   | ReturnsCPR  -- Yes, this function returns a constructed product
555                 -- Implicitly, this means "after the function has been applied
556                 -- to all its arguments", so the worker/wrapper builder in 
557                 -- WwLib.mkWWcpr checks that that it is indeed saturated before
558                 -- making use of the CPR info
559
560         -- We used to keep nested info about sub-components, but
561         -- we never used it so I threw it away
562
563 seqCpr :: CprInfo -> ()
564 seqCpr ReturnsCPR = ()
565 seqCpr NoCPRInfo  = ()
566
567 noCprInfo       = NoCPRInfo
568
569 ppCprInfo NoCPRInfo  = empty
570 ppCprInfo ReturnsCPR = ptext SLIT("__M")
571
572 instance Outputable CprInfo where
573     ppr = ppCprInfo
574
575 instance Show CprInfo where
576     showsPrec p c = showsPrecSDoc p (ppr c)
577 #endif
578 \end{code}
579
580
581 %************************************************************************
582 %*                                                                      *
583 \subsection[lbvar-IdInfo]{Lambda-bound var info about an @Id@}
584 %*                                                                      *
585 %************************************************************************
586
587 If the @Id@ is a lambda-bound variable then it may have lambda-bound
588 var info.  Sometimes we know whether the lambda binding this var is a
589 ``one-shot'' lambda; that is, whether it is applied at most once.
590
591 This information may be useful in optimisation, as computations may
592 safely be floated inside such a lambda without risk of duplicating
593 work.
594
595 \begin{code}
596 data LBVarInfo = NoLBVarInfo 
597                | IsOneShotLambda        -- The lambda is applied at most once).
598
599 seqLBVar l = l `seq` ()
600 \end{code}
601
602 \begin{code}
603 hasNoLBVarInfo NoLBVarInfo     = True
604 hasNoLBVarInfo IsOneShotLambda = False
605
606 noLBVarInfo = NoLBVarInfo
607
608 pprLBVarInfo NoLBVarInfo     = empty
609 pprLBVarInfo IsOneShotLambda = ptext SLIT("OneShot")
610
611 instance Outputable LBVarInfo where
612     ppr = pprLBVarInfo
613
614 instance Show LBVarInfo where
615     showsPrec p c = showsPrecSDoc p (ppr c)
616 \end{code}
617
618
619 %************************************************************************
620 %*                                                                      *
621 \subsection{Bulk operations on IdInfo}
622 %*                                                                      *
623 %************************************************************************
624
625 @zapLamInfo@ is used for lambda binders that turn out to to be
626 part of an unsaturated lambda
627
628 \begin{code}
629 zapLamInfo :: IdInfo -> Maybe IdInfo
630 zapLamInfo info@(IdInfo {occInfo = occ, newDemandInfo = demand})
631   | is_safe_occ occ && is_safe_dmd demand
632   = Nothing
633   | otherwise
634   = Just (info {occInfo = safe_occ, newDemandInfo = Nothing})
635   where
636         -- The "unsafe" occ info is the ones that say I'm not in a lambda
637         -- because that might not be true for an unsaturated lambda
638     is_safe_occ (OneOcc in_lam once) = in_lam
639     is_safe_occ other                = True
640
641     safe_occ = case occ of
642                  OneOcc _ once -> OneOcc insideLam once
643                  other         -> occ
644
645     is_safe_dmd Nothing    = True
646     is_safe_dmd (Just dmd) = not (isStrictDmd dmd)
647 \end{code}
648
649 \begin{code}
650 zapDemandInfo :: IdInfo -> Maybe IdInfo
651 zapDemandInfo info@(IdInfo {newDemandInfo = dmd})
652   | isJust dmd = Just (info {newDemandInfo = Nothing})
653   | otherwise  = Nothing
654 \end{code}
655