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