69a26403b97d9ca3dc4665e0757fab47d9a66257
[ghc-hetmet.git] / ghc / compiler / stranal / SaAbsInt.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1993-1996
3 %
4 \section[SaAbsInt]{Abstract interpreter for strictness analysis}
5
6 \begin{code}
7 #include "HsVersions.h"
8
9 module SaAbsInt (
10         findStrictness,
11         findDemand,
12         absEval,
13         widen,
14         fixpoint,
15         isBot
16     ) where
17
18 IMP_Ubiq(){-uitous-}
19
20 import CoreSyn
21 import CoreUnfold       ( Unfolding(..), UfExpr, RdrName, SimpleUnfolding(..), FormSummary )
22 import CoreUtils        ( unTagBinders )
23 import Id               ( idType, getIdStrictness, getIdUnfolding,
24                           dataConTyCon, dataConArgTys, SYN_IE(Id)
25                         )
26 import IdInfo           ( StrictnessInfo(..),
27                           wwPrim, wwStrict, wwEnum, wwUnpack
28                         )
29 import Demand           ( Demand(..) )
30 import MagicUFs         ( MagicUnfoldingFun )
31 import Maybes           ( maybeToBool )
32 import Outputable       ( Outputable(..){-instance * []-} )
33 import PprStyle         ( PprStyle(..) )
34 import Pretty           ( Doc, ptext )
35 import PrimOp           ( PrimOp(..) )
36 import SaLib
37 import TyCon            ( maybeTyConSingleCon, isEnumerationTyCon,
38                           TyCon{-instance Eq-}
39                         )
40 import Type             ( maybeAppDataTyConExpandingDicts, 
41                           isPrimType, SYN_IE(Type) )
42 import TysWiredIn       ( intTyCon, integerTyCon, doubleTyCon,
43                           floatTyCon, wordTyCon, addrTyCon
44                         )
45 import Util             ( isIn, isn'tIn, nOfThem, zipWithEqual,
46                           pprTrace, panic, pprPanic, assertPanic
47                         )
48
49 returnsRealWorld x = False -- ToDo: panic "SaAbsInt.returnsRealWorld (ToDo)"
50 \end{code}
51
52 %************************************************************************
53 %*                                                                      *
54 \subsection[AbsVal-ops]{Operations on @AbsVals@}
55 %*                                                                      *
56 %************************************************************************
57
58 Least upper bound, greatest lower bound.
59
60 \begin{code}
61 lub, glb :: AbsVal -> AbsVal -> AbsVal
62
63 lub val1 val2 | isBot val1    = val2    -- The isBot test includes the case where
64 lub val1 val2 | isBot val2    = val1    -- one of the val's is a function which
65                                         -- always returns bottom, such as \y.x,
66                                         -- when x is bound to bottom.
67
68 lub (AbsProd xs) (AbsProd ys) = AbsProd (zipWithEqual "lub" lub xs ys)
69
70 lub _             _           = AbsTop  -- Crude, but conservative
71                                         -- The crudity only shows up if there
72                                         -- are functions involved
73
74 -- Slightly funny glb; for absence analysis only;
75 -- AbsBot is the safe answer.
76 --
77 -- Using anyBot rather than just testing for AbsBot is important.
78 -- Consider:
79 --
80 --   f = \a b -> ...
81 --
82 --   g = \x y z -> case x of
83 --                   []     -> f x
84 --                   (p:ps) -> f p
85 --
86 -- Now, the abstract value of the branches of the case will be an
87 -- AbsFun, but when testing for z's absence we want to spot that it's
88 -- an AbsFun which can't possibly return AbsBot.  So when glb'ing we
89 -- mustn't be too keen to bale out and return AbsBot; the anyBot test
90 -- spots that (f x) can't possibly return AbsBot.
91
92 -- We have also tripped over the following interesting case:
93 --      case x of
94 --        []     -> \y -> 1
95 --        (p:ps) -> f
96 --
97 -- Now, suppose f is bound to AbsTop.  Does this expression mention z?
98 -- Obviously not.  But the case will take the glb of AbsTop (for f) and
99 -- an AbsFun (for \y->1). We should not bale out and give AbsBot, because
100 -- that would say that it *does* mention z (or anything else for that matter).
101 -- Nor can we always return AbsTop, because the AbsFun might be something
102 -- like (\y->z), which obviously does mention z. The point is that we're
103 -- glbing two functions, and AbsTop is not actually the top of the function
104 -- lattice.  It is more like (\xyz -> x|y|z); that is, AbsTop returns
105 -- poison iff any of its arguments do.
106
107 -- Deal with functions specially, because AbsTop isn't the
108 -- top of their domain.
109
110 glb v1 v2
111   | is_fun v1 || is_fun v2
112   = if not (anyBot v1) && not (anyBot v2)
113     then
114         AbsTop
115     else
116         AbsBot
117   where
118     is_fun (AbsFun _ _ _)     = True
119     is_fun (AbsApproxFun _ _) = True    -- Not used, but the glb works ok
120     is_fun other              = False
121
122 -- The non-functional cases are quite straightforward
123
124 glb (AbsProd xs) (AbsProd ys) = AbsProd (zipWithEqual "glb" glb xs ys)
125
126 glb AbsTop       v2           = v2
127 glb v1           AbsTop       = v1
128
129 glb _            _            = AbsBot          -- Be pessimistic
130
131
132
133 combineCaseValues
134         :: AnalysisKind
135         -> AbsVal       -- Value of scrutinee
136         -> [AbsVal]     -- Value of branches (at least one)
137         -> AbsVal       -- Result
138
139 -- For strictness analysis, see if the scrutinee is bottom; if so
140 -- return bottom; otherwise, the lub of the branches.
141
142 combineCaseValues StrAnal AbsBot          branches = AbsBot
143 combineCaseValues StrAnal other_scrutinee branches
144         -- Scrutinee can only be AbsBot, AbsProd or AbsTop
145   = ASSERT(ok_scrutinee)
146     foldr1 lub branches
147   where
148     ok_scrutinee
149       = case other_scrutinee of {
150           AbsTop    -> True;    -- i.e., cool
151           AbsProd _ -> True;    -- ditto
152           _         -> False    -- party over
153         }
154
155 -- For absence analysis, check if the scrutinee is all poison (isBot)
156 -- If so, return poison (AbsBot); otherwise, any nested poison will come
157 -- out from looking at the branches, so just glb together the branches
158 -- to get the worst one.
159
160 combineCaseValues AbsAnal AbsBot          branches = AbsBot
161 combineCaseValues AbsAnal other_scrutinee branches
162         -- Scrutinee can only be AbsBot, AbsProd or AbsTop
163   = ASSERT(ok_scrutinee)
164     let
165         result = foldr1 glb branches
166
167         tracer = if at_least_one_AbsFun && at_least_one_AbsTop
168                     && no_AbsBots then
169                     pprTrace "combineCase:" (ppr PprDebug branches)
170                  else
171                     id
172     in
173 --    tracer (
174     result
175 --    )
176   where
177     ok_scrutinee
178       = case other_scrutinee of {
179           AbsTop    -> True;    -- i.e., cool
180           AbsProd _ -> True;    -- ditto
181           _         -> False    -- party over
182         }
183
184     at_least_one_AbsFun = foldr ((||) . is_AbsFun) False branches
185     at_least_one_AbsTop = foldr ((||) . is_AbsTop) False branches
186     no_AbsBots = foldr ((&&) . is_not_AbsBot) True branches
187
188     is_AbsFun x = case x of { AbsFun _ _ _ -> True; _ -> False }
189     is_AbsTop x = case x of { AbsTop -> True; _ -> False }
190     is_not_AbsBot x = case x of { AbsBot -> False; _ -> True }
191 \end{code}
192
193 @isBot@ returns True if its argument is (a representation of) bottom.  The
194 ``representation'' part is because we need to detect the bottom {\em function}
195 too.  To detect the bottom function, bind its args to top, and see if it
196 returns bottom.
197
198 Used only in strictness analysis:
199 \begin{code}
200 isBot :: AbsVal -> Bool
201
202 isBot AbsBot                = True
203 isBot (AbsFun arg body env) = isBot (absEval StrAnal body env)
204                                -- Don't bother to extend the envt because
205                                -- unbound variables default to AbsTop anyway
206 isBot other                 = False
207 \end{code}
208
209 Used only in absence analysis:
210 \begin{code}
211 anyBot :: AbsVal -> Bool
212
213 anyBot AbsBot                 = True    -- poisoned!
214 anyBot AbsTop                 = False
215 anyBot (AbsProd vals)         = any anyBot vals
216 anyBot (AbsFun arg body env)  = anyBot (absEval AbsAnal body env)
217 anyBot (AbsApproxFun _ _)     = False
218
219     -- AbsApproxFun can only arise in absence analysis from the Demand
220     -- info of an imported value; whatever it is we're looking for is
221     -- certainly not present over in the imported value.
222 \end{code}
223
224 @widen@ takes an @AbsVal@, $val$, and returns and @AbsVal@ which is
225 approximated by $val$.  Furthermore, the result has no @AbsFun@s in
226 it, so it can be compared for equality by @sameVal@.
227
228 \begin{code}
229 widen :: AnalysisKind -> AbsVal -> AbsVal
230
231 widen StrAnal (AbsFun arg body env)
232   = AbsApproxFun (findDemandStrOnly env body arg)
233                  (widen StrAnal abs_body)
234   where
235     abs_body = absEval StrAnal body env
236
237 {-      OLD comment... 
238         This stuff is now instead handled neatly by the fact that AbsApproxFun 
239         contains an AbsVal inside it.   SLPJ Jan 97
240
241   | isBot abs_body = AbsBot
242     -- It's worth checking for a function which is unconditionally
243     -- bottom.  Consider
244     --
245     --  f x y = let g y = case x of ...
246     --          in (g ..) + (g ..)
247     --
248     -- Here, when we are considering strictness of f in x, we'll
249     -- evaluate the body of f with x bound to bottom.  The current
250     -- strategy is to bind g to its *widened* value; without the isBot
251     -- (...) test above, we'd bind g to an AbsApproxFun, and deliver
252     -- Top, not Bot as the value of f's rhs.  The test spots the
253     -- unconditional bottom-ness of g when x is bottom.  (Another
254     -- alternative here would be to bind g to its exact abstract
255     -- value, but that entails lots of potential re-computation, at
256     -- every application of g.)
257 -}
258
259 widen StrAnal (AbsProd vals) = AbsProd (map (widen StrAnal) vals)
260 widen StrAnal other_val      = other_val
261
262
263 widen AbsAnal (AbsFun arg body env)
264   | anyBot abs_body = AbsBot
265         -- In the absence-analysis case it's *essential* to check
266         -- that the function has no poison in its body.  If it does,
267         -- anywhere, then the whole function is poisonous.
268
269   | otherwise
270   = AbsApproxFun (findDemandAbsOnly env body arg)
271                  (widen AbsAnal abs_body)
272   where
273     abs_body = absEval AbsAnal body env
274
275 widen AbsAnal (AbsProd vals) = AbsProd (map (widen AbsAnal) vals)
276
277         -- It's desirable to do a good job of widening for product
278         -- values.  Consider
279         --
280         --      let p = (x,y)
281         --      in ...(case p of (x,y) -> x)...
282         --
283         -- Now, is y absent in this expression?  Currently the
284         -- analyser widens p before looking at p's scope, to avoid
285         -- lots of recomputation in the case where p is a function.
286         -- So if widening doesn't have a case for products, we'll
287         -- widen p to AbsBot (since when searching for absence in y we
288         -- bind y to poison ie AbsBot), and now we are lost.
289
290 widen AbsAnal other_val = other_val
291
292 -- WAS:   if anyBot val then AbsBot else AbsTop
293 -- Nowadays widen is doing a better job on functions for absence analysis.
294 \end{code}
295
296 @crudeAbsWiden@ is used just for absence analysis, and always
297 returns AbsTop or AbsBot, so it widens to a two-point domain
298
299 \begin{code}
300 crudeAbsWiden :: AbsVal -> AbsVal
301 crudeAbsWiden val = if anyBot val then AbsBot else AbsTop
302 \end{code}
303
304 @sameVal@ compares two abstract values for equality.  It can't deal with
305 @AbsFun@, but that should have been removed earlier in the day by @widen@.
306
307 \begin{code}
308 sameVal :: AbsVal -> AbsVal -> Bool     -- Can't handle AbsFun!
309
310 #ifdef DEBUG
311 sameVal (AbsFun _ _ _) _ = panic "sameVal: AbsFun: arg1"
312 sameVal _ (AbsFun _ _ _) = panic "sameVal: AbsFun: arg2"
313 #endif
314
315 sameVal AbsBot AbsBot = True
316 sameVal AbsBot other  = False   -- widen has reduced AbsFun bots to AbsBot
317
318 sameVal AbsTop AbsTop = True
319 sameVal AbsTop other  = False           -- Right?
320
321 sameVal (AbsProd vals1) (AbsProd vals2) = and (zipWithEqual "sameVal" sameVal vals1 vals2)
322 sameVal (AbsProd _)     AbsTop          = False
323 sameVal (AbsProd _)     AbsBot          = False
324
325 sameVal (AbsApproxFun str1 v1) (AbsApproxFun str2 v2) = str1 == str2 && sameVal v1 v1
326 sameVal (AbsApproxFun _ _)     AbsTop                 = False
327 sameVal (AbsApproxFun _ _)     AbsBot                 = False
328
329 sameVal val1 val2 = panic "sameVal: type mismatch or AbsFun encountered"
330 \end{code}
331
332
333 @evalStrictness@ compares a @Demand@ with an abstract value, returning
334 @True@ iff the abstract value is {\em less defined} than the demand.
335 (@True@ is the exciting answer; @False@ is always safe.)
336
337 \begin{code}
338 evalStrictness :: Demand
339                -> AbsVal
340                -> Bool          -- True iff the value is sure
341                                 -- to be less defined than the Demand
342
343 evalStrictness (WwLazy _) _   = False
344 evalStrictness WwStrict   val = isBot val
345 evalStrictness WwEnum     val = isBot val
346
347 evalStrictness (WwUnpack _ demand_info) val
348   = case val of
349       AbsTop       -> False
350       AbsBot       -> True
351       AbsProd vals -> or (zipWithEqual "evalStrictness" evalStrictness demand_info vals)
352       _            -> trace "evalStrictness?" False
353
354 evalStrictness WwPrim val
355   = case val of
356       AbsTop -> False
357
358       other  ->   -- A primitive value should be defined, never bottom;
359                   -- hence this paranoia check
360                 pprPanic "evalStrictness: WwPrim:" (ppr PprDebug other)
361 \end{code}
362
363 For absence analysis, we're interested in whether "poison" in the
364 argument (ie a bottom therein) can propagate to the result of the
365 function call; that is, whether the specified demand can {\em
366 possibly} hit poison.
367
368 \begin{code}
369 evalAbsence (WwLazy True) _ = False     -- Can't possibly hit poison
370                                         -- with Absent demand
371
372 evalAbsence (WwUnpack _ demand_info) val
373   = case val of
374         AbsTop       -> False           -- No poison in here
375         AbsBot       -> True            -- Pure poison
376         AbsProd vals -> or (zipWithEqual "evalAbsence" evalAbsence demand_info vals)
377         _            -> panic "evalAbsence: other"
378
379 evalAbsence other val = anyBot val
380   -- The demand is conservative; even "Lazy" *might* evaluate the
381   -- argument arbitrarily so we have to look everywhere for poison
382 \end{code}
383
384 %************************************************************************
385 %*                                                                      *
386 \subsection[absEval]{Evaluate an expression in the abstract domain}
387 %*                                                                      *
388 %************************************************************************
389
390 \begin{code}
391 -- The isBottomingId stuf is now dealt with via the Id's strictness info
392 -- absId anal var env | isBottomingId var
393 --   = case anal of
394 --      StrAnal -> AbsBot       -- See discussion below
395 --      AbsAnal -> AbsTop       -- Just want to see if there's any poison in
396                                 -- error's arg
397
398 absId anal var env
399   = let
400      result =
401       case (lookupAbsValEnv env var, getIdStrictness var, getIdUnfolding var) of
402
403         (Just abs_val, _, _) ->
404                         abs_val -- Bound in the environment
405
406         (Nothing, NoStrictnessInfo, CoreUnfolding (SimpleUnfolding _ _ unfolding)) ->
407                         -- We have an unfolding for the expr
408                         -- Assume the unfolding has no free variables since it
409                         -- came from inside the Id
410                         absEval anal (unTagBinders unfolding) env
411                 -- Notice here that we only look in the unfolding if we don't
412                 -- have strictness info (an unusual situation).
413                 -- We could have chosen to look in the unfolding if it exists,
414                 -- and only try the strictness info if it doesn't, and that would
415                 -- give more accurate results, at the cost of re-abstract-interpreting
416                 -- the unfolding every time.
417                 -- We found only one place where the look-at-unfolding-first
418                 -- method gave better results, which is in the definition of
419                 -- showInt in the Prelude.  In its defintion, fromIntegral is
420                 -- not inlined (it's big) but ab-interp-ing its unfolding gave
421                 -- a better result than looking at its strictness only.
422                 --  showInt :: Integral a => a -> [Char] -> [Char]
423                 -- !       {-# GHC_PRAGMA _A_ 1 _U_ 122 _S_
424                 --         "U(U(U(U(SA)AAAAAAAAL)AA)AAAAASAAASA)" {...} _N_ _N_ #-}
425                 -- --- 42,44 ----
426                 --   showInt :: Integral a => a -> [Char] -> [Char]
427                 -- !       {-# GHC_PRAGMA _A_ 1 _U_ 122 _S_
428                 --        "U(U(U(U(SL)LLLLLLLLL)LL)LLLLLSLLLLL)" _N_ _N_ #-}
429
430
431         (Nothing, strictness_info, _) ->
432                         -- Includes MagicUnfolding, NoUnfolding
433                         -- Try the strictness info
434                         absValFromStrictness anal strictness_info
435     in
436     -- pprTrace "absId:" (hcat [ppr PprDebug var, ptext SLIT("=:"), pp_anal anal, text SLIT(":="),ppr PprDebug result]) $
437     result
438   where
439     pp_anal StrAnal = ptext SLIT("STR")
440     pp_anal AbsAnal = ptext SLIT("ABS")
441
442 absEvalAtom anal (VarArg v) env = absId anal v env
443 absEvalAtom anal (LitArg _) env = AbsTop
444 \end{code}
445
446 \begin{code}
447 absEval :: AnalysisKind -> CoreExpr -> AbsValEnv -> AbsVal
448
449 absEval anal (Var var) env = absId anal var env
450
451 absEval anal (Lit _) env = AbsTop
452     -- What if an unboxed literal?  That's OK: it terminates, so its
453     -- abstract value is AbsTop.
454
455     -- For absence analysis, a literal certainly isn't the "poison" variable
456 \end{code}
457
458 Discussion about \tr{error} (following/quoting Lennart): Any expression
459 \tr{error e} is regarded as bottom (with HBC, with the
460 \tr{-ffail-strict} flag, on with \tr{-O}).
461
462 Regarding it as bottom gives much better strictness properties for
463 some functions.  E.g.
464 \begin{verbatim}
465         f [x] y = x+y
466         f (x:xs) y = f xs (x+y)
467 i.e.
468         f [] _ = error "no match"
469         f [x] y = x+y
470         f (x:xs) y = f xs (x+y)
471 \end{verbatim}
472 is strict in \tr{y}, which you really want.  But, it may lead to
473 transformations that turn a call to \tr{error} into non-termination.
474 (The odds of this happening aren't good.)
475
476
477 Things are a little different for absence analysis, because we want
478 to make sure that any poison (?????)
479
480 \begin{code}
481 absEval StrAnal (Prim SeqOp [TyArg _, e]) env
482   = ASSERT(isValArg e)
483     if isBot (absEvalAtom StrAnal e env) then AbsBot else AbsTop
484         -- This is a special case to ensure that seq# is strict in its argument.
485         -- The comments below (for most normal PrimOps) do not apply.
486
487 absEval StrAnal (Prim op es) env = AbsTop
488         -- The arguments are all of unboxed type, so they will already
489         -- have been eval'd.  If the boxed version was bottom, we'll
490         -- already have returned bottom.
491
492         -- Actually, I believe we are saying that either (1) the
493         -- primOp uses unboxed args and they've been eval'ed, so
494         -- there's no need to force strictness here, _or_ the primOp
495         -- uses boxed args and we don't know whether or not it's
496         -- strict, so we assume laziness. (JSM)
497
498 absEval AbsAnal (Prim op as) env
499   = if any anyBot [absEvalAtom AbsAnal a env | a <- as, isValArg a]
500     then AbsBot
501     else AbsTop
502         -- For absence analysis, we want to see if the poison shows up...
503
504 absEval anal (Con con as) env
505   | has_single_con
506   = AbsProd [absEvalAtom anal a env | a <- as, isValArg a]
507
508   | otherwise   -- Not single-constructor
509   = case anal of
510         StrAnal ->      -- Strictness case: it's easy: it certainly terminates
511                    AbsTop
512         AbsAnal ->      -- In the absence case we need to be more
513                         -- careful: look to see if there's any
514                         -- poison in the components
515                    if any anyBot [absEvalAtom AbsAnal a env | a <- as, isValArg a]
516                    then AbsBot
517                    else AbsTop
518   where
519     has_single_con = maybeToBool (maybeTyConSingleCon (dataConTyCon con))
520 \end{code}
521
522 \begin{code}
523 absEval anal (Lam (ValBinder binder) body) env
524   = AbsFun binder body env
525 absEval anal (Lam other_binder expr) env
526   = absEval  anal expr env
527 absEval anal (App f a) env | isValArg a
528   = absApply anal (absEval anal f env) (absEvalAtom anal a env)
529 absEval anal (App expr _) env
530   = absEval anal expr env
531 \end{code}
532
533 For primitive cases, just GLB the branches, then LUB with the expr part.
534
535 \begin{code}
536 absEval anal (Case expr (PrimAlts alts deflt)) env
537   = let
538         expr_val    = absEval anal expr env
539         abs_alts    = [ absEval anal rhs env | (_, rhs) <- alts ]
540                         -- Don't bother to extend envt, because unbound vars
541                         -- default to the conservative AbsTop
542
543         abs_deflt   = absEvalDefault anal expr_val deflt env
544     in
545         combineCaseValues anal expr_val
546                                (abs_deflt ++ abs_alts)
547
548 absEval anal (Case expr (AlgAlts alts deflt)) env
549   = let
550         expr_val  = absEval anal expr env
551         abs_alts  = [ absEvalAlgAlt anal expr_val alt env | alt <- alts ]
552         abs_deflt = absEvalDefault anal expr_val deflt env
553     in
554     let
555         result =
556           combineCaseValues anal expr_val
557                                 (abs_deflt ++ abs_alts)
558     in
559 {-
560     (case anal of
561         StrAnal -> id
562         _ -> pprTrace "absCase:ABS:" (($$) (hsep [ppr PprDebug expr, ppr PprDebug result, ppr PprDebug expr_val, ppr PprDebug abs_deflt, ppr PprDebug abs_alts]) (ppr PprDebug (keysFM env `zip` eltsFM env)))
563     )
564 -}
565     result
566 \end{code}
567
568 For @Lets@ we widen the value we get.  This is nothing to
569 do with fixpointing.  The reason is so that we don't get an explosion
570 in the amount of computation.  For example, consider:
571 \begin{verbatim}
572       let
573         g a = case a of
574                 q1 -> ...
575                 q2 -> ...
576         f x = case x of
577                 p1 -> ...g r...
578                 p2 -> ...g s...
579       in
580         f e
581 \end{verbatim}
582 If we bind @f@ and @g@ to their exact abstract value, then we'll
583 ``execute'' one call to @f@ and {\em two} calls to @g@.  This can blow
584 up exponentially.  Widening cuts it off by making a fixed
585 approximation to @f@ and @g@, so that the bodies of @f@ and @g@ are
586 not evaluated again at all when they are called.
587
588 Of course, this can lose useful joint strictness, which is sad.  An
589 alternative approach would be to try with a certain amount of ``fuel''
590 and be prepared to bale out.
591
592 \begin{code}
593 absEval anal (Let (NonRec binder e1) e2) env
594   = let
595         new_env = addOneToAbsValEnv env binder (widen anal (absEval anal e1 env))
596     in
597         -- The binder of a NonRec should *not* be of unboxed type,
598         -- hence no need to strictly evaluate the Rhs.
599     absEval anal e2 new_env
600
601 absEval anal (Let (Rec pairs) body) env
602   = let
603         (binders,rhss) = unzip pairs
604         rhs_vals = cheapFixpoint anal binders rhss env  -- Returns widened values
605         new_env  = growAbsValEnvList env (binders `zip` rhs_vals)
606     in
607     absEval anal body new_env
608
609 absEval anal (SCC cc expr)      env = absEval anal expr env
610 absEval anal (Coerce c ty expr) env = absEval anal expr env
611 \end{code}
612
613 \begin{code}
614 absEvalAlgAlt :: AnalysisKind -> AbsVal -> (Id,[Id],CoreExpr) -> AbsValEnv -> AbsVal
615
616 absEvalAlgAlt anal (AbsProd arg_vals) (con, args, rhs) env
617   =     -- The scrutinee is a product value, so it must be of a single-constr
618         -- type; so the constructor in this alternative must be the right one
619         -- so we can go ahead and bind the constructor args to the components
620         -- of the product value.
621     ASSERT(length arg_vals == length args)
622     let
623          new_env = growAbsValEnvList env (args `zip` arg_vals)
624     in
625     absEval anal rhs new_env
626
627 absEvalAlgAlt anal other_scrutinee (con, args, rhs) env
628   =     -- Scrutinised value is Top or Bot (it can't be a function!)
629         -- So just evaluate the rhs with all constr args bound to Top.
630         -- (If the scrutinee is Top we'll never evaluated this function
631         -- call anyway!)
632     ASSERT(ok_scrutinee)
633     absEval anal rhs env
634   where
635     ok_scrutinee
636       = case other_scrutinee of {
637           AbsTop -> True;   -- i.e., OK
638           AbsBot -> True;   -- ditto
639           _      -> False   -- party over
640         }
641
642
643 absEvalDefault :: AnalysisKind
644                -> AbsVal                -- Value of scrutinee
645                -> CoreCaseDefault
646                -> AbsValEnv
647                -> [AbsVal]              -- Empty or singleton
648
649 absEvalDefault anal scrut_val NoDefault env = []
650 absEvalDefault anal scrut_val (BindDefault binder expr) env
651   = [absEval anal expr (addOneToAbsValEnv env binder scrut_val)]
652 \end{code}
653
654 %************************************************************************
655 %*                                                                      *
656 \subsection[absApply]{Apply an abstract function to an abstract argument}
657 %*                                                                      *
658 %************************************************************************
659
660 Easy ones first:
661
662 \begin{code}
663 absApply :: AnalysisKind -> AbsVal -> AbsVal -> AbsVal
664
665 absApply anal AbsBot arg = AbsBot
666   -- AbsBot represents the abstract bottom *function* too
667
668 absApply StrAnal AbsTop arg = AbsTop
669 absApply AbsAnal AbsTop arg = if anyBot arg
670                               then AbsBot
671                               else AbsTop
672         -- To be conservative, we have to assume that a function about
673         -- which we know nothing (AbsTop) might look at some part of
674         -- its argument
675 \end{code}
676
677 An @AbsFun@ with only one more argument needed---bind it and eval the
678 result.  A @Lam@ with two or more args: return another @AbsFun@ with
679 an augmented environment.
680
681 \begin{code}
682 absApply anal (AbsFun binder body env) arg
683   = absEval anal body (addOneToAbsValEnv env binder arg)
684 \end{code}
685
686 \begin{code}
687 absApply StrAnal (AbsApproxFun demand val) arg
688   = if evalStrictness demand arg
689     then AbsBot
690     else val
691
692 absApply AbsAnal (AbsApproxFun demand val) arg
693   = if evalAbsence demand arg
694     then AbsBot
695     else val
696
697 #ifdef DEBUG
698 absApply anal (AbsProd _)       arg = panic ("absApply: Duff function: AbsProd." ++ show anal)
699 #endif
700 \end{code}
701
702
703
704
705 %************************************************************************
706 %*                                                                      *
707 \subsection[findStrictness]{Determine some binders' strictness}
708 %*                                                                      *
709 %************************************************************************
710
711 @findStrictness@ applies the function \tr{\ ids -> expr} to
712 \tr{[bot,top,top,...]}, \tr{[top,bot,top,top,...]}, etc., (i.e., once
713 with @AbsBot@ in each argument position), and evaluates the resulting
714 abstract value; it returns a vector of @Demand@s saying whether the
715 result of doing this is guaranteed to be bottom.  This tells the
716 strictness of the function in each of the arguments.
717
718 If an argument is of unboxed type, then we declare that function to be
719 strict in that argument.
720
721 We don't really have to make up all those lists of mostly-@AbsTops@;
722 unbound variables in an @AbsValEnv@ are implicitly mapped to that.
723
724 See notes on @addStrictnessInfoToId@.
725
726 \begin{code}
727 findStrictness :: StrAnalFlags
728                -> [Type]        -- Types of args in which strictness is wanted
729                -> AbsVal        -- Abstract strictness value of function
730                -> AbsVal        -- Abstract absence value of function
731                -> [Demand]      -- Resulting strictness annotation
732
733 findStrictness strflags [] str_val abs_val = []
734
735 findStrictness strflags (ty:tys) str_val abs_val
736   = let
737         demand       = findRecDemand strflags [] str_fn abs_fn ty
738         str_fn val   = absApply StrAnal str_val val
739         abs_fn val   = absApply AbsAnal abs_val val
740
741         demands = findStrictness strflags tys
742                         (absApply StrAnal str_val AbsTop)
743                         (absApply AbsAnal abs_val AbsTop)
744     in
745     demand : demands
746 \end{code}
747
748
749 \begin{code}
750 findDemandStrOnly str_env expr binder   -- Only strictness environment available
751   = findRecDemand strflags [] str_fn abs_fn (idType binder)
752   where
753     str_fn val = absEval StrAnal expr (addOneToAbsValEnv str_env binder val)
754     abs_fn val = AbsBot         -- Always says poison; so it looks as if
755                                 -- nothing is absent; safe
756     strflags   = getStrAnalFlags str_env
757
758 findDemandAbsOnly abs_env expr binder   -- Only absence environment available
759   = findRecDemand strflags [] str_fn abs_fn (idType binder)
760   where
761     str_fn val = AbsBot         -- Always says non-termination;
762                                 -- that'll make findRecDemand peer into the
763                                 -- structure of the value.
764     abs_fn val = absEval AbsAnal expr (addOneToAbsValEnv abs_env binder val)
765     strflags   = getStrAnalFlags abs_env
766
767
768 findDemand str_env abs_env expr binder
769   = findRecDemand strflags [] str_fn abs_fn (idType binder)
770   where
771     str_fn val = absEval StrAnal expr (addOneToAbsValEnv str_env binder val)
772     abs_fn val = absEval AbsAnal expr (addOneToAbsValEnv abs_env binder val)
773     strflags   = getStrAnalFlags str_env
774 \end{code}
775
776 @findRecDemand@ is where we finally convert strictness/absence info
777 into ``Demands'' which we can pin on Ids (etc.).
778
779 NOTE: What do we do if something is {\em both} strict and absent?
780 Should \tr{f x y z = error "foo"} says that \tr{f}'s arguments are all
781 strict (because of bottoming effect of \tr{error}) or all absent
782 (because they're not used)?
783
784 Well, for practical reasons, we prefer absence over strictness.  In
785 particular, it makes the ``default defaults'' for class methods (the
786 ones that say \tr{defm.foo dict = error "I don't exist"}) come out
787 nicely [saying ``the dict isn't used''], rather than saying it is
788 strict in every component of the dictionary [massive gratuitious
789 casing to take the dict apart].
790
791 But you could have examples where going for strictness would be better
792 than absence.  Consider:
793 \begin{verbatim}
794         let x = something big
795         in
796         f x y z + g x
797 \end{verbatim}
798
799 If \tr{x} is marked absent in \tr{f}, but not strict, and \tr{g} is
800 lazy, then the thunk for \tr{x} will be built.  If \tr{f} was strict,
801 then we'd let-to-case it:
802 \begin{verbatim}
803         case something big of
804           x -> f x y z + g x
805 \end{verbatim}
806 Ho hum.
807
808 \begin{code}
809 findRecDemand :: StrAnalFlags
810               -> [TyCon]            -- TyCons already seen; used to avoid
811                                     -- zooming into recursive types
812               -> (AbsVal -> AbsVal) -- The strictness function
813               -> (AbsVal -> AbsVal) -- The absence function
814               -> Type       -- The type of the argument
815               -> Demand
816
817 findRecDemand strflags seen str_fn abs_fn ty
818   = if isPrimType ty then -- It's a primitive type!
819        wwPrim
820
821     else if not (anyBot (abs_fn AbsBot)) then -- It's absent
822        -- We prefer absence over strictness: see NOTE above.
823        WwLazy True
824
825     else if not (all_strict ||
826                  (num_strict && is_numeric_type ty) ||
827                  (isBot (str_fn AbsBot))) then
828         WwLazy False -- It's not strict and we're not pretending
829
830     else -- It's strict (or we're pretending it is)!
831
832        case (maybeAppDataTyConExpandingDicts ty) of
833
834          Nothing    -> wwStrict
835
836          Just (tycon,tycon_arg_tys,[data_con]) | tycon `not_elem` seen ->
837            -- Single constructor case, tycon not already seen higher up
838            let
839               cmpnt_tys = dataConArgTys data_con tycon_arg_tys
840               prod_len = length cmpnt_tys
841
842               compt_strict_infos
843                 = [ findRecDemand strflags (tycon:seen)
844                          (\ cmpnt_val ->
845                                str_fn (mkMainlyTopProd prod_len i cmpnt_val)
846                          )
847                          (\ cmpnt_val ->
848                                abs_fn (mkMainlyTopProd prod_len i cmpnt_val)
849                          )
850                      cmpnt_ty
851                   | (cmpnt_ty, i) <- cmpnt_tys `zip` [1..] ]
852            in
853            if null compt_strict_infos then
854                  if isEnumerationTyCon tycon then wwEnum else wwStrict
855            else
856                  wwUnpack compt_strict_infos
857           where
858            not_elem = isn'tIn "findRecDemand"
859
860          Just (tycon,_,_) ->
861                 -- Multi-constr data types, *or* an abstract data
862                 -- types, *or* things we don't have a way of conveying
863                 -- the info over module boundaries (class ops,
864                 -- superdict sels, dfns).
865             if isEnumerationTyCon tycon then
866                 wwEnum
867             else
868                 wwStrict
869   where
870     (all_strict, num_strict) = strflags
871
872     is_numeric_type ty
873       = case (maybeAppDataTyConExpandingDicts ty) of -- NB: duplicates stuff done above
874           Nothing -> False
875           Just (tycon, _, _)
876             | tycon `is_elem`
877               [intTyCon, integerTyCon,
878                doubleTyCon, floatTyCon,
879                wordTyCon, addrTyCon]
880             -> True
881           _{-something else-} -> False
882       where
883         is_elem = isIn "is_numeric_type"
884
885     -- mkMainlyTopProd: make an AbsProd that is all AbsTops ("n"-1 of
886     -- them) except for a given value in the "i"th position.
887
888     mkMainlyTopProd :: Int -> Int -> AbsVal -> AbsVal
889
890     mkMainlyTopProd n i val
891       = let
892             befores = nOfThem (i-1) AbsTop
893             afters  = nOfThem (n-i) AbsTop
894         in
895         AbsProd (befores ++ (val : afters))
896 \end{code}
897
898 %************************************************************************
899 %*                                                                      *
900 \subsection[fixpoint]{Fixpointer for the strictness analyser}
901 %*                                                                      *
902 %************************************************************************
903
904 The @fixpoint@ functions take a list of \tr{(binder, expr)} pairs, an
905 environment, and returns the abstract value of each binder.
906
907 The @cheapFixpoint@ function makes a conservative approximation,
908 by binding each of the variables to Top in their own right hand sides.
909 That allows us to make rapid progress, at the cost of a less-than-wonderful
910 approximation.
911
912 \begin{code}
913 cheapFixpoint :: AnalysisKind -> [Id] -> [CoreExpr] -> AbsValEnv -> [AbsVal]
914
915 cheapFixpoint AbsAnal [id] [rhs] env
916   = [crudeAbsWiden (absEval AbsAnal rhs new_env)]
917   where
918     new_env = addOneToAbsValEnv env id AbsTop   -- Unsafe starting point!
919                     -- In the just-one-binding case, we guarantee to
920                     -- find a fixed point in just one iteration,
921                     -- because we are using only a two-point domain.
922                     -- This improves matters in cases like:
923                     --
924                     --  f x y = letrec g = ...g...
925                     --          in g x
926                     --
927                     -- Here, y isn't used at all, but if g is bound to
928                     -- AbsBot we simply get AbsBot as the next
929                     -- iteration too.
930
931 cheapFixpoint anal ids rhss env
932   = [widen anal (absEval anal rhs new_env) | rhs <- rhss]
933                 -- We do just one iteration, starting from a safe
934                 -- approximation.  This won't do a good job in situations
935                 -- like:
936                 --      \x -> letrec f = ...g...
937                 --                   g = ...f...x...
938                 --            in
939                 --            ...f...
940                 -- Here, f will end up bound to Top after one iteration,
941                 -- and hence we won't spot the strictness in x.
942                 -- (A second iteration would solve this.  ToDo: try the effect of
943                 --  really searching for a fixed point.)
944   where
945     new_env = growAbsValEnvList env [(id,safe_val) | id <- ids]
946
947     safe_val
948       = case anal of    -- The safe starting point
949           StrAnal -> AbsTop
950           AbsAnal -> AbsBot
951 \end{code}
952
953 \begin{verbatim}
954 mkLookupFun :: (key -> key -> Bool)     -- Equality predicate
955             -> (key -> key -> Bool)     -- Less-than predicate
956             -> [(key,val)]              -- The assoc list
957             -> key                      -- The key
958             -> Maybe val                -- The corresponding value
959
960 mkLookupFun eq lt alist s
961   = case [a | (s',a) <- alist, s' `eq` s] of
962       []    -> Nothing
963       (a:_) -> Just a
964 \end{verbatim}
965
966 \begin{code}
967 fixpoint :: AnalysisKind -> [Id] -> [CoreExpr] -> AbsValEnv -> [AbsVal]
968
969 fixpoint anal [] _ env = []
970
971 fixpoint anal ids rhss env
972   = fix_loop initial_vals
973   where
974     initial_val id
975       = case anal of    -- The (unsafe) starting point
976           StrAnal -> if (returnsRealWorld (idType id))
977                      then AbsTop -- this is a massively horrible hack (SLPJ 95/05)
978                      else AbsBot
979           AbsAnal -> AbsTop
980
981     initial_vals = [ initial_val id | id <- ids ]
982
983     fix_loop :: [AbsVal] -> [AbsVal]
984
985     fix_loop current_widened_vals
986       = let
987             new_env  = growAbsValEnvList env (ids `zip` current_widened_vals)
988             new_vals = [ absEval anal rhs new_env | rhs <- rhss ]
989             new_widened_vals = map (widen anal) new_vals
990         in
991         if (and (zipWith sameVal current_widened_vals new_widened_vals)) then
992             current_widened_vals
993
994             -- NB: I was too chicken to make that a zipWithEqual,
995             -- lest I jump into a black hole.  WDP 96/02
996
997             -- Return the widened values.  We might get a slightly
998             -- better value by returning new_vals (which we used to
999             -- do, see below), but alas that means that whenever the
1000             -- function is called we have to re-execute it, which is
1001             -- expensive.
1002
1003             -- OLD VERSION
1004             -- new_vals
1005             -- Return the un-widened values which may be a bit better
1006             -- than the widened ones, and are guaranteed safe, since
1007             -- they are one iteration beyond current_widened_vals,
1008             -- which itself is a fixed point.
1009         else
1010             fix_loop new_widened_vals
1011 \end{code}
1012
1013 For absence analysis, we make do with a very very simple approach:
1014 look for convergence in a two-point domain.
1015
1016 We used to use just one iteration, starting with the variables bound
1017 to @AbsBot@, which is safe.
1018
1019 Prior to that, we used one iteration starting from @AbsTop@ (which
1020 isn't safe).  Why isn't @AbsTop@ safe?  Consider:
1021 \begin{verbatim}
1022         letrec
1023           x = ...p..d...
1024           d = (x,y)
1025         in
1026         ...
1027 \end{verbatim}
1028 Here, if p is @AbsBot@, then we'd better {\em not} end up with a ``fixed
1029 point'' of @d@ being @(AbsTop, AbsTop)@!  An @AbsBot@ initial value is
1030 safe because it gives poison more often than really necessary, and
1031 thus may miss some absence, but will never claim absence when it ain't
1032 so.
1033
1034 Anyway, one iteration starting with everything bound to @AbsBot@ give
1035 bad results for
1036
1037         f = \ x -> ...f...
1038
1039 Here, f would always end up bound to @AbsBot@, which ain't very
1040 clever, because then it would introduce poison whenever it was
1041 applied.  Much better to start with f bound to @AbsTop@, and widen it
1042 to @AbsBot@ if any poison shows up. In effect we look for convergence
1043 in the two-point @AbsTop@/@AbsBot@ domain.
1044
1045 What we miss (compared with the cleverer strictness analysis) is
1046 spotting that in this case
1047
1048         f = \ x y -> ...y...(f x y')...
1049
1050 \tr{x} is actually absent, since it is only passed round the loop, never
1051 used.  But who cares about missing that?
1052
1053 NB: despite only having a two-point domain, we may still have many
1054 iterations, because there are several variables involved at once.