2ca9e83dc8e79dd99d8a9a72e8dd3ad2effdf4fd
[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 = addRecBinds env [ (binder, libCase env_body rhs)
191                                    | (binder, rhs) <- pairs ]
192
193     rhs_small_enough rhs = couldBeSmallEnoughToInline lIBERATE_BOMB_SIZE rhs
194     lIBERATE_BOMB_SIZE   = bombOutSize env
195 \end{code}
196
197
198 Expressions
199 ~~~~~~~~~~~
200
201 \begin{code}
202 libCase :: LibCaseEnv
203         -> CoreExpr
204         -> CoreExpr
205
206 libCase env (Var v)             = libCaseId env v
207 libCase env (Lit lit)           = Lit lit
208 libCase env (Type ty)           = Type ty
209 libCase env (App fun arg)       = App (libCase env fun) (libCase env arg)
210 libCase env (Note note body)    = Note note (libCase env body)
211
212 libCase env (Lam binder body)
213   = Lam binder (libCase (addBinders env [binder]) body)
214
215 libCase env (Let bind body)
216   = Let bind' (libCase env_body body)
217   where
218     (env_body, bind') = libCaseBind env bind
219
220 libCase env (Case scrut bndr alts)
221   = Case (libCase env scrut) bndr (map (libCaseAlt env_alts) alts)
222   where
223     env_alts = addBinders env_with_scrut [bndr]
224     env_with_scrut = case scrut of
225                         Var scrut_var -> addScrutedVar env scrut_var
226                         other         -> env
227
228 libCaseAlt env (con,args,rhs) = (con, args, libCase (addBinders env args) rhs)
229 \end{code}
230
231 Ids
232 ~~~
233 \begin{code}
234 libCaseId :: LibCaseEnv -> Id -> CoreExpr
235 libCaseId env v
236   | Just the_bind <- lookupRecId env v, -- It's a use of a recursive thing
237     there_are_free_scruts               -- with free vars scrutinised in RHS
238   = Let the_bind (Var v)
239
240   | otherwise
241   = Var v
242
243   where
244     rec_id_level          = lookupLevel env v
245     there_are_free_scruts = freeScruts env rec_id_level
246 \end{code}
247
248
249
250 Utility functions
251 ~~~~~~~~~~~~~~~~~
252 \begin{code}
253 addBinders :: LibCaseEnv -> [CoreBndr] -> LibCaseEnv
254 addBinders (LibCaseEnv bomb lvl lvl_env rec_env scruts) binders
255   = LibCaseEnv bomb lvl lvl_env' rec_env scruts
256   where
257     lvl_env' = extendVarEnvList lvl_env (binders `zip` repeat lvl)
258
259 addRecBinds :: LibCaseEnv -> [(Id,CoreExpr)] -> LibCaseEnv
260 addRecBinds (LibCaseEnv bomb lvl lvl_env rec_env scruts) pairs
261   = LibCaseEnv bomb lvl' lvl_env' rec_env' scruts
262   where
263     lvl'     = lvl + 1
264     lvl_env' = extendVarEnvList lvl_env [(binder,lvl) | (binder,_) <- pairs]
265     rec_env' = extendVarEnvList rec_env [(binder, Rec pairs) | (binder,_) <- pairs]
266
267 addScrutedVar :: LibCaseEnv
268               -> Id             -- This Id is being scrutinised by a case expression
269               -> LibCaseEnv
270
271 addScrutedVar env@(LibCaseEnv bomb lvl lvl_env rec_env scruts) scrut_var
272   | bind_lvl < lvl
273   = LibCaseEnv bomb lvl lvl_env rec_env scruts'
274         -- Add to scruts iff the scrut_var is being scrutinised at
275         -- a deeper level than its defn
276
277   | otherwise = env
278   where
279     scruts'  = (scrut_var, lvl) : scruts
280     bind_lvl = case lookupVarEnv lvl_env scrut_var of
281                  Just lvl -> lvl
282                  Nothing  -> topLevel
283
284 lookupRecId :: LibCaseEnv -> Id -> Maybe CoreBind
285 lookupRecId (LibCaseEnv bomb lvl lvl_env rec_env scruts) id
286 #ifndef DEBUG
287   = lookupVarEnv rec_env id
288 #else
289   = case (lookupVarEnv rec_env id) of
290       xxx@(Just _) -> xxx
291       xxx          -> xxx
292 #endif
293
294 lookupLevel :: LibCaseEnv -> Id -> LibCaseLevel
295 lookupLevel (LibCaseEnv bomb lvl lvl_env rec_env scruts) id
296   = case lookupVarEnv lvl_env id of
297       Just lvl -> lvl
298       Nothing  -> topLevel
299
300 freeScruts :: LibCaseEnv
301            -> LibCaseLevel      -- Level of the recursive Id
302            -> Bool              -- True <=> there is an enclosing case of a variable
303                                 -- bound outside (ie level <=) the recursive Id.
304 freeScruts (LibCaseEnv bomb lvl lvl_env rec_env scruts) rec_bind_lvl
305   = not (null free_scruts)
306   where
307     free_scruts = [v | (v,lvl) <- scruts, lvl <= rec_bind_lvl]
308 \end{code}