[project @ 2001-12-14 17:24:03 by simonpj]
[ghc-hetmet.git] / ghc / compiler / simplCore / FloatOut.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[FloatOut]{Float bindings outwards (towards the top level)}
5
6 ``Long-distance'' floating of bindings towards the top level.
7
8 \begin{code}
9 module FloatOut ( floatOutwards ) where
10
11 #include "HsVersions.h"
12
13 import CoreSyn
14 import CoreUtils        ( mkSCC )
15
16 import CmdLineOpts      ( DynFlags, DynFlag(..), FloatOutSwitches(..) )
17 import ErrUtils         ( dumpIfSet_dyn )
18 import CostCentre       ( dupifyCC, CostCentre )
19 import Id               ( Id )
20 import CoreLint         ( showPass, endPass )
21 import SetLevels        ( setLevels, isInlineCtxt,
22                           Level(..), tOP_LEVEL, ltMajLvl, ltLvl, isTopLvl
23                         )
24 import UniqSupply       ( UniqSupply )
25 import List             ( partition )
26 import Outputable
27 \end{code}
28
29         -----------------
30         Overall game plan
31         -----------------
32
33 The Big Main Idea is:
34
35         To float out sub-expressions that can thereby get outside
36         a non-one-shot value lambda, and hence may be shared.
37
38
39 To achieve this we may need to do two thing:
40
41    a) Let-bind the sub-expression:
42
43         f (g x)  ==>  let lvl = f (g x) in lvl
44
45       Now we can float the binding for 'lvl'.  
46
47    b) More than that, we may need to abstract wrt a type variable
48
49         \x -> ... /\a -> let v = ...a... in ....
50
51       Here the binding for v mentions 'a' but not 'x'.  So we
52       abstract wrt 'a', to give this binding for 'v':
53
54             vp = /\a -> ...a...
55             v  = vp a
56
57       Now the binding for vp can float out unimpeded.
58       I can't remember why this case seemed important enough to
59       deal with, but I certainly found cases where important floats
60       didn't happen if we did not abstract wrt tyvars.
61
62 With this in mind we can also achieve another goal: lambda lifting.
63 We can make an arbitrary (function) binding float to top level by
64 abstracting wrt *all* local variables, not just type variables, leaving
65 a binding that can be floated right to top level.  Whether or not this
66 happens is controlled by a flag.
67
68
69 Random comments
70 ~~~~~~~~~~~~~~~
71
72 At the moment we never float a binding out to between two adjacent
73 lambdas.  For example:
74
75 @
76         \x y -> let t = x+x in ...
77 ===>
78         \x -> let t = x+x in \y -> ...
79 @
80 Reason: this is less efficient in the case where the original lambda
81 is never partially applied.
82
83 But there's a case I've seen where this might not be true.  Consider:
84 @
85 elEm2 x ys
86   = elem' x ys
87   where
88     elem' _ []  = False
89     elem' x (y:ys)      = x==y || elem' x ys
90 @
91 It turns out that this generates a subexpression of the form
92 @
93         \deq x ys -> let eq = eqFromEqDict deq in ...
94 @
95 vwhich might usefully be separated to
96 @
97         \deq -> let eq = eqFromEqDict deq in \xy -> ...
98 @
99 Well, maybe.  We don't do this at the moment.
100
101 \begin{code}
102 type LevelledExpr  = TaggedExpr Level
103 type LevelledBind  = TaggedBind Level
104 type FloatBind     = (Level, CoreBind)
105 type FloatBinds    = [FloatBind]
106 \end{code}
107
108 %************************************************************************
109 %*                                                                      *
110 \subsection[floatOutwards]{@floatOutwards@: let-floating interface function}
111 %*                                                                      *
112 %************************************************************************
113
114 \begin{code}
115 floatOutwards :: DynFlags
116               -> FloatOutSwitches
117               -> UniqSupply 
118               -> [CoreBind] -> IO [CoreBind]
119
120 floatOutwards dflags float_sws us pgm
121   = do {
122         showPass dflags float_msg ;
123
124         let { annotated_w_levels = setLevels float_sws pgm us ;
125               (fss, binds_s')    = unzip (map floatTopBind annotated_w_levels)
126             } ;
127
128         dumpIfSet_dyn dflags Opt_D_verbose_core2core "Levels added:"
129                   (vcat (map ppr annotated_w_levels));
130
131         let { (tlets, ntlets, lams) = get_stats (sum_stats fss) };
132
133         dumpIfSet_dyn dflags Opt_D_dump_simpl_stats "FloatOut stats:"
134                 (hcat [ int tlets,  ptext SLIT(" Lets floated to top level; "),
135                         int ntlets, ptext SLIT(" Lets floated elsewhere; from "),
136                         int lams,   ptext SLIT(" Lambda groups")]);
137
138         endPass dflags float_msg  Opt_D_verbose_core2core (concat binds_s')
139                         {- no specific flag for dumping float-out -} 
140     }
141   where
142     float_msg = showSDoc (text "Float out" <+> parens (sws float_sws))
143     sws (FloatOutSw lam const) = pp_not lam   <+> text "lambdas" <> comma <+>
144                                  pp_not const <+> text "constants"
145     pp_not True  = empty
146     pp_not False = text "not"
147
148 floatTopBind bind@(NonRec _ _)
149   = case (floatBind bind) of { (fs, floats, bind') ->
150     (fs, floatsToBinds floats ++ [bind'])
151     }
152
153 floatTopBind bind@(Rec _)
154   = case (floatBind bind) of { (fs, floats, Rec pairs') ->
155     WARN( not (null floats), ppr bind $$ ppr floats )
156     (fs, [Rec (floatsToBindPairs floats ++ pairs')]) }
157 \end{code}
158
159 %************************************************************************
160 %*                                                                      *
161 \subsection[FloatOut-Bind]{Floating in a binding (the business end)}
162 %*                                                                      *
163 %************************************************************************
164
165
166 \begin{code}
167 floatBind :: LevelledBind
168           -> (FloatStats, FloatBinds, CoreBind)
169
170 floatBind (NonRec (name,level) rhs)
171   = case (floatRhs level rhs) of { (fs, rhs_floats, rhs') ->
172     (fs, rhs_floats, NonRec name rhs') }
173
174 floatBind bind@(Rec pairs)
175   = case (unzip3 (map do_pair pairs)) of { (fss, rhss_floats, new_pairs) ->
176
177     if not (isTopLvl bind_level) then
178         -- Standard case
179         (sum_stats fss, concat rhss_floats, Rec new_pairs)
180     else
181         -- In a recursive binding, *destined for* the top level
182         -- (only), the rhs floats may contain references to the 
183         -- bound things.  For example
184         --
185         --      f = ...(let v = ...f... in b) ...
186         --
187         --  might get floated to
188         --
189         --      v = ...f...
190         --      f = ... b ...
191         --
192         -- and hence we must (pessimistically) make all the floats recursive
193         -- with the top binding.  Later dependency analysis will unravel it.
194         --
195         -- Can't happen on nested bindings because floatRhs will dump
196         -- the bindings in the RHS (partitionByMajorLevel treats top specially)
197         (sum_stats fss, [],
198          Rec (new_pairs ++ floatsToBindPairs (concat rhss_floats)))
199     }
200   where
201     bind_level = getBindLevel bind
202
203     do_pair ((name, level), rhs)
204       = case (floatRhs level rhs) of { (fs, rhs_floats, rhs') ->
205         (fs, rhs_floats, (name, rhs'))
206         }
207 \end{code}
208
209 %************************************************************************
210
211 \subsection[FloatOut-Expr]{Floating in expressions}
212 %*                                                                      *
213 %************************************************************************
214
215 \begin{code}
216 floatExpr, floatRhs
217          :: Level
218          -> LevelledExpr
219          -> (FloatStats, FloatBinds, CoreExpr)
220
221 floatRhs lvl arg
222   = case (floatExpr lvl arg) of { (fsa, floats, arg') ->
223     case (partitionByMajorLevel lvl floats) of { (floats', heres) ->
224         -- Dump bindings that aren't going to escape from a lambda
225         -- This is to avoid floating the x binding out of
226         --      f (let x = e in b)
227         -- unnecessarily.  It even causes a bug to do so if we have
228         --      y = writeArr# a n (let x = e in b)
229         -- because the y binding is an expr-ok-for-speculation one.
230         -- [SLPJ Dec 01: I don't understand this last comment; 
231         --               writeArr# is not ok-for-spec because of its side effect]
232     (fsa, floats', install heres arg') }}
233
234 floatExpr _ (Var v)   = (zeroStats, [], Var v)
235 floatExpr _ (Type ty) = (zeroStats, [], Type ty)
236 floatExpr _ (Lit lit) = (zeroStats, [], Lit lit)
237           
238 floatExpr lvl (App e a)
239   = case (floatExpr lvl e) of { (fse, floats_e, e') ->
240     case (floatRhs  lvl a) of { (fsa, floats_a, a') ->
241     (fse `add_stats` fsa, floats_e ++ floats_a, App e' a') }}
242
243 floatExpr lvl lam@(Lam _ _)
244   = let
245         (bndrs_w_lvls, body) = collectBinders lam
246         (bndrs, lvls)        = unzip bndrs_w_lvls
247
248         -- For the all-tyvar case we are prepared to pull 
249         -- the lets out, to implement the float-out-of-big-lambda
250         -- transform; but otherwise we only float bindings that are
251         -- going to escape a value lambda.
252         -- In particular, for one-shot lambdas we don't float things
253         -- out; we get no saving by so doing.
254         partition_fn | all isTyVar bndrs = partitionByLevel
255                      | otherwise         = partitionByMajorLevel
256     in
257     case (floatExpr (last lvls) body) of { (fs, floats, body') ->
258
259         -- Dump any bindings which absolutely cannot go any further
260     case (partition_fn (head lvls) floats)      of { (floats', heres) ->
261
262     (add_to_stats fs floats', floats', mkLams bndrs (install heres body'))
263     }}
264
265 floatExpr lvl (Note note@(SCC cc) expr)
266   = case (floatExpr lvl expr)    of { (fs, floating_defns, expr') ->
267     let
268         -- Annotate bindings floated outwards past an scc expression
269         -- with the cc.  We mark that cc as "duplicated", though.
270
271         annotated_defns = annotate (dupifyCC cc) floating_defns
272     in
273     (fs, annotated_defns, Note note expr') }
274   where
275     annotate :: CostCentre -> FloatBinds -> FloatBinds
276
277     annotate dupd_cc defn_groups
278       = [ (level, ann_bind floater) | (level, floater) <- defn_groups ]
279       where
280         ann_bind (NonRec binder rhs)
281           = NonRec binder (mkSCC dupd_cc rhs)
282
283         ann_bind (Rec pairs)
284           = Rec [(binder, mkSCC dupd_cc rhs) | (binder, rhs) <- pairs]
285
286 floatExpr lvl (Note InlineMe expr)      -- Other than SCCs
287   = case floatExpr InlineCtxt expr of { (fs, floating_defns, expr') ->
288     WARN( not (null floating_defns),
289           ppr expr $$ ppr floating_defns )      -- We do no floating out of Inlines
290     (fs, [], Note InlineMe expr') }     -- See notes in SetLevels
291
292 floatExpr lvl (Note note expr)  -- Other than SCCs
293   = case (floatExpr lvl expr)    of { (fs, floating_defns, expr') ->
294     (fs, floating_defns, Note note expr') }
295
296 floatExpr lvl (Let bind body)
297   = case (floatBind bind)     of { (fsb, rhs_floats,  bind') ->
298     case (floatExpr lvl body) of { (fse, body_floats, body') ->
299 --    if isInlineCtxt lvl then  -- No floating inside an InlineMe
300 --      ASSERT( null rhs_floats && null body_floats )
301 --      (add_stats fsb fse, [], Let bind' body')
302 --    else
303         (add_stats fsb fse,
304          rhs_floats ++ [(bind_lvl, bind')] ++ body_floats,
305          body')
306     }}
307   where
308     bind_lvl = getBindLevel bind
309
310 floatExpr lvl (Case scrut (case_bndr, case_lvl) alts)
311   = case floatExpr lvl scrut    of { (fse, fde, scrut') ->
312     case floatList float_alt alts       of { (fsa, fda, alts')  ->
313     (add_stats fse fsa, fda ++ fde, Case scrut' case_bndr alts')
314     }}
315   where
316         -- Use floatRhs for the alternatives, so that we
317         -- don't gratuitiously float bindings out of the RHSs
318     float_alt (con, bs, rhs)
319         = case (floatRhs case_lvl rhs)  of { (fs, rhs_floats, rhs') ->
320           (fs, rhs_floats, (con, map fst bs, rhs')) }
321
322
323 floatList :: (a -> (FloatStats, FloatBinds, b)) -> [a] -> (FloatStats, FloatBinds, [b])
324 floatList f [] = (zeroStats, [], [])
325 floatList f (a:as) = case f a            of { (fs_a,  binds_a,  b)  ->
326                      case floatList f as of { (fs_as, binds_as, bs) ->
327                      (fs_a `add_stats` fs_as, binds_a ++ binds_as, b:bs) }}
328 \end{code}
329
330 %************************************************************************
331 %*                                                                      *
332 \subsection{Utility bits for floating stats}
333 %*                                                                      *
334 %************************************************************************
335
336 I didn't implement this with unboxed numbers.  I don't want to be too
337 strict in this stuff, as it is rarely turned on.  (WDP 95/09)
338
339 \begin{code}
340 data FloatStats
341   = FlS Int  -- Number of top-floats * lambda groups they've been past
342         Int  -- Number of non-top-floats * lambda groups they've been past
343         Int  -- Number of lambda (groups) seen
344
345 get_stats (FlS a b c) = (a, b, c)
346
347 zeroStats = FlS 0 0 0
348
349 sum_stats xs = foldr add_stats zeroStats xs
350
351 add_stats (FlS a1 b1 c1) (FlS a2 b2 c2)
352   = FlS (a1 + a2) (b1 + b2) (c1 + c2)
353
354 add_to_stats (FlS a b c) floats
355   = FlS (a + length top_floats) (b + length other_floats) (c + 1)
356   where
357     (top_floats, other_floats) = partition to_very_top floats
358
359     to_very_top (my_lvl, _) = isTopLvl my_lvl
360 \end{code}
361
362
363 %************************************************************************
364 %*                                                                      *
365 \subsection{Utility bits for floating}
366 %*                                                                      *
367 %************************************************************************
368
369 \begin{code}
370 getBindLevel (NonRec (_, lvl) _)      = lvl
371 getBindLevel (Rec (((_,lvl), _) : _)) = lvl
372 \end{code}
373
374 \begin{code}
375 partitionByMajorLevel, partitionByLevel
376         :: Level                -- Partitioning level
377
378         -> FloatBinds           -- Defns to be divided into 2 piles...
379
380         -> (FloatBinds, -- Defns  with level strictly < partition level,
381             FloatBinds) -- The rest
382
383
384 partitionByMajorLevel ctxt_lvl defns
385   = partition float_further defns
386   where
387         -- Float it if we escape a value lambda, or if we get to the top level
388     float_further (my_lvl, bind) = my_lvl `ltMajLvl` ctxt_lvl || isTopLvl my_lvl
389         -- The isTopLvl part says that if we can get to the top level, say "yes" anyway
390         -- This means that 
391         --      x = f e
392         -- transforms to 
393         --    lvl = e
394         --    x = f lvl
395         -- which is as it should be
396
397 partitionByLevel ctxt_lvl defns
398   = partition float_further defns
399   where
400     float_further (my_lvl, _) = my_lvl `ltLvl` ctxt_lvl
401 \end{code}
402
403 \begin{code}
404 floatsToBinds :: FloatBinds -> [CoreBind]
405 floatsToBinds floats = map snd floats
406
407 floatsToBindPairs :: FloatBinds -> [(Id,CoreExpr)]
408
409 floatsToBindPairs floats = concat (map mk_pairs floats)
410   where
411    mk_pairs (_, Rec pairs)         = pairs
412    mk_pairs (_, NonRec binder rhs) = [(binder,rhs)]
413
414 install :: FloatBinds -> CoreExpr -> CoreExpr
415
416 install defn_groups expr
417   = foldr install_group expr defn_groups
418   where
419     install_group (_, defns) body = Let defns body
420 \end{code}