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