[project @ 2000-12-06 13:03:28 by simonmar]
[ghc-hetmet.git] / ghc / compiler / simplCore / LiberateCase.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1998
3 %
4 \section[LiberateCase]{Unroll recursion to allow evals to be lifted from a loop}
5
6 \begin{code}
7 module LiberateCase ( liberateCase ) where
8
9 #include "HsVersions.h"
10
11 import CmdLineOpts      ( DynFlags, DynFlag(..), dopt, opt_LiberateCaseThreshold )
12 import CoreLint         ( showPass, endPass )
13 import CoreSyn
14 import CoreUnfold       ( couldBeSmallEnoughToInline )
15 import Var              ( Id )
16 import VarEnv
17 import Maybes
18 \end{code}
19
20 This module walks over @Core@, and looks for @case@ on free variables.
21 The criterion is:
22         if there is case on a free on the route to the recursive call,
23         then the recursive call is replaced with an unfolding.
24
25 Example
26
27 \begin{verbatim}
28 f = \ t -> case v of
29                V a b -> a : f t
30 \end{verbatim}
31
32 => the inner f is replaced.
33
34 \begin{verbatim}
35 f = \ t -> case v of
36                V a b -> a : (letrec
37                                 f =  \ t -> case v of
38                                                V a b -> a : f t
39                              in f) t
40 \end{verbatim}
41 (note the NEED for shadowing)
42
43 => Run Andr\'e's wonder pass ...
44 \begin{verbatim}
45 f = \ t -> case v of
46                V a b -> a : (letrec
47                                 f = \ t -> a : f t
48                              in f t)
49 \begin{verbatim}
50 Better code, because 'a' is  free inside the inner letrec, rather
51 than needing projection from v.
52
53 Other examples we'd like to catch with this kind of transformation
54
55         last []     = error 
56         last (x:[]) = x
57         last (x:xs) = last xs
58
59 We'd like to avoid the redundant pattern match, transforming to
60
61         last [] = error
62         last (x:[]) = x
63         last (x:(y:ys)) = last' y ys
64                 where
65                   last' y []     = y
66                   last' _ (y:ys) = last' y ys
67
68         (is this necessarily an improvement)
69
70
71 Similarly drop:
72
73         drop n [] = []
74         drop 0 xs = xs
75         drop n (x:xs) = drop (n-1) xs
76
77 Would like to pass n along unboxed.
78         
79
80 To think about (Apr 94)
81 ~~~~~~~~~~~~~~
82
83 Main worry: duplicating code excessively.  At the moment we duplicate
84 the entire binding group once at each recursive call.  But there may
85 be a group of recursive calls which share a common set of evaluated
86 free variables, in which case the duplication is a plain waste.
87
88 Another thing we could consider adding is some unfold-threshold thing,
89 so that we'll only duplicate if the size of the group rhss isn't too
90 big.
91
92 Data types
93 ~~~~~~~~~~
94
95 The ``level'' of a binder tells how many
96 recursive defns lexically enclose the binding
97 A recursive defn "encloses" its RHS, not its
98 scope.  For example:
99 \begin{verbatim}
100         letrec f = let g = ... in ...
101         in
102         let h = ...
103         in ...
104 \end{verbatim}
105 Here, the level of @f@ is zero, the level of @g@ is one,
106 and the level of @h@ is zero (NB not one).
107
108 \begin{code}
109 type LibCaseLevel = Int
110
111 topLevel :: LibCaseLevel
112 topLevel = 0
113 \end{code}
114
115 \begin{code}
116 data LibCaseEnv
117   = LibCaseEnv
118         Int                     -- Bomb-out size for deciding if
119                                 -- potential liberatees are too big.
120                                 -- (passed in from cmd-line args)
121
122         LibCaseLevel            -- Current level
123
124         (IdEnv LibCaseLevel)    -- Binds all non-top-level in-scope Ids
125                                 -- (top-level and imported things have
126                                 -- a level of zero)
127
128         (IdEnv CoreBind)-- Binds *only* recursively defined
129                                 -- Ids, to their own binding group,
130                                 -- and *only* in their own RHSs
131
132         [(Id,LibCaseLevel)]     -- Each of these Ids was scrutinised by an
133                                 -- enclosing case expression, with the
134                                 -- specified number of enclosing
135                                 -- recursive bindings; furthermore,
136                                 -- the Id is bound at a lower level
137                                 -- than the case expression.  The
138                                 -- order is insignificant; it's a bag
139                                 -- really
140
141 initEnv :: Int -> LibCaseEnv
142 initEnv bomb_size = LibCaseEnv bomb_size 0 emptyVarEnv emptyVarEnv []
143
144 bombOutSize (LibCaseEnv bomb_size _ _ _ _) = bomb_size
145 \end{code}
146
147
148 Programs
149 ~~~~~~~~
150 \begin{code}
151 liberateCase :: DynFlags -> [CoreBind] -> IO [CoreBind]
152 liberateCase dflags binds
153   = do {
154         showPass dflags "Liberate case" ;
155         let { binds' = do_prog (initEnv opt_LiberateCaseThreshold) binds } ;
156         endPass dflags "Liberate case" Opt_D_verbose_core2core binds'
157                                 {- no specific flag for dumping -} 
158     }
159   where
160     do_prog env [] = []
161     do_prog env (bind:binds) = bind' : do_prog env' binds
162                              where
163                                (env', bind') = libCaseBind env bind
164 \end{code}
165
166 Bindings
167 ~~~~~~~~
168
169 \begin{code}
170 libCaseBind :: LibCaseEnv -> CoreBind -> (LibCaseEnv, CoreBind)
171
172 libCaseBind env (NonRec binder rhs)
173   = (addBinders env [binder], NonRec binder (libCase env rhs))
174
175 libCaseBind env (Rec pairs)
176   = (env_body, Rec pairs')
177   where
178     (binders, rhss) = unzip pairs
179
180     env_body = addBinders env binders
181
182     pairs' = [(binder, libCase env_rhs rhs) | (binder,rhs) <- pairs]
183
184     env_rhs = if all rhs_small_enough rhss then extended_env else env
185
186         -- We extend the rec-env by binding each Id to its rhs, first
187         -- processing the rhs with an *un-extended* environment, so
188         -- that the same process doesn't occur for ever!
189
190     extended_env
191       = addRecBinds env [ (binder, libCase env_body rhs)
192                         | (binder, rhs) <- pairs ]
193
194         -- Why "localiseId" above?  Because we're creating a new local
195         -- copy of the original binding.  In particular, the original
196         -- binding might have been for a top-level, and this copy clearly
197         -- will not be top-level!
198
199         -- It is enough to change just the binder, because subsequent
200         -- simplification will propagate the right info from the binder.
201
202         -- Why does it matter?  Because the codeGen keeps a separate
203         -- environment for top-level Ids, and it is disastrous for it
204         -- to think that something is top-level when it isn't.
205         --
206         -- [May 98: all this is now handled by SimplCore.tidyCore]
207
208     rhs_small_enough rhs = couldBeSmallEnoughToInline lIBERATE_BOMB_SIZE rhs
209
210     lIBERATE_BOMB_SIZE = bombOutSize env
211 \end{code}
212
213
214 Expressions
215 ~~~~~~~~~~~
216
217 \begin{code}
218 libCase :: LibCaseEnv
219         -> CoreExpr
220         -> CoreExpr
221
222 libCase env (Var v)             = libCaseId env v
223 libCase env (Lit lit)           = Lit lit
224 libCase env (Type ty)           = Type ty
225 libCase env (App fun arg)       = App (libCase env fun) (libCase env arg)
226 libCase env (Note note body)    = Note note (libCase env body)
227
228 libCase env (Lam binder body)
229   = Lam binder (libCase (addBinders env [binder]) body)
230
231 libCase env (Let bind body)
232   = Let bind' (libCase env_body body)
233   where
234     (env_body, bind') = libCaseBind env bind
235
236 libCase env (Case scrut bndr alts)
237   = Case (libCase env scrut) bndr (map (libCaseAlt env_alts) alts)
238   where
239     env_alts = addBinders env_with_scrut [bndr]
240     env_with_scrut = case scrut of
241                         Var scrut_var -> addScrutedVar env scrut_var
242                         other         -> env
243
244 libCaseAlt env (con,args,rhs) = (con, args, libCase (addBinders env args) rhs)
245 \end{code}
246
247 Ids
248 ~~~
249 \begin{code}
250 libCaseId :: LibCaseEnv -> Id -> CoreExpr
251 libCaseId env v
252   | maybeToBool maybe_rec_bind &&       -- It's a use of a recursive thing
253     there_are_free_scruts               -- with free vars scrutinised in RHS
254   = Let the_bind (Var v)
255
256   | otherwise
257   = Var v
258
259   where
260     maybe_rec_bind :: Maybe CoreBind    -- The binding of the recursive thingy
261     maybe_rec_bind = lookupRecId env v
262     Just the_bind  = maybe_rec_bind
263
264     rec_id_level = lookupLevel env v
265
266     there_are_free_scruts = freeScruts env rec_id_level
267 \end{code}
268
269
270
271 Utility functions
272 ~~~~~~~~~~~~~~~~~
273 \begin{code}
274 addBinders :: LibCaseEnv -> [CoreBndr] -> LibCaseEnv
275 addBinders (LibCaseEnv bomb lvl lvl_env rec_env scruts) binders
276   = LibCaseEnv bomb lvl lvl_env' rec_env scruts
277   where
278     lvl_env' = extendVarEnvList lvl_env (binders `zip` repeat lvl)
279
280 addRecBinds :: LibCaseEnv -> [(Id,CoreExpr)] -> LibCaseEnv
281 addRecBinds (LibCaseEnv bomb lvl lvl_env rec_env scruts) pairs
282   = LibCaseEnv bomb lvl' lvl_env' rec_env' scruts
283   where
284     lvl'     = lvl + 1
285     lvl_env' = extendVarEnvList lvl_env [(binder,lvl) | (binder,_) <- pairs]
286     rec_env' = extendVarEnvList rec_env [(binder, Rec pairs) | (binder,_) <- pairs]
287
288 addScrutedVar :: LibCaseEnv
289               -> Id             -- This Id is being scrutinised by a case expression
290               -> LibCaseEnv
291
292 addScrutedVar env@(LibCaseEnv bomb lvl lvl_env rec_env scruts) scrut_var
293   | bind_lvl < lvl
294   = LibCaseEnv bomb lvl lvl_env rec_env scruts'
295         -- Add to scruts iff the scrut_var is being scrutinised at
296         -- a deeper level than its defn
297
298   | otherwise = env
299   where
300     scruts'  = (scrut_var, lvl) : scruts
301     bind_lvl = case lookupVarEnv lvl_env scrut_var of
302                  Just lvl -> lvl
303                  Nothing  -> topLevel
304
305 lookupRecId :: LibCaseEnv -> Id -> Maybe CoreBind
306 lookupRecId (LibCaseEnv bomb lvl lvl_env rec_env scruts) id
307 #ifndef DEBUG
308   = lookupVarEnv rec_env id
309 #else
310   = case (lookupVarEnv rec_env id) of
311       xxx@(Just _) -> xxx
312       xxx          -> xxx
313 #endif
314
315 lookupLevel :: LibCaseEnv -> Id -> LibCaseLevel
316 lookupLevel (LibCaseEnv bomb lvl lvl_env rec_env scruts) id
317   = case lookupVarEnv lvl_env id of
318       Just lvl -> lvl
319       Nothing  -> topLevel
320
321 freeScruts :: LibCaseEnv
322            -> LibCaseLevel      -- Level of the recursive Id
323            -> Bool              -- True <=> there is an enclosing case of a variable
324                                 -- bound outside (ie level <=) the recursive Id.
325 freeScruts (LibCaseEnv bomb lvl lvl_env rec_env scruts) rec_bind_lvl
326   = not (null free_scruts)
327   where
328     free_scruts = [v | (v,lvl) <- scruts, lvl > rec_bind_lvl]
329 \end{code}