2 % (c) The AQUA Project, Glasgow University, 1994-1998
4 \section[LiberateCase]{Unroll recursion to allow evals to be lifted from a loop}
7 module LiberateCase ( liberateCase ) where
9 #include "HsVersions.h"
11 import CmdLineOpts ( DynFlags, DynFlag(..), opt_LiberateCaseThreshold )
12 import CoreLint ( showPass, endPass )
14 import CoreUnfold ( couldBeSmallEnoughToInline )
18 import Util ( notNull )
21 This module walks over @Core@, and looks for @case@ on free variables.
23 if there is case on a free on the route to the recursive call,
24 then the recursive call is replaced with an unfolding.
33 => the inner f is replaced.
42 (note the NEED for shadowing)
53 Better code, because 'a' is free inside the inner letrec, rather
54 than needing projection from v.
56 Other examples we'd like to catch with this kind of transformation
62 We'd like to avoid the redundant pattern match, transforming to
66 last (x:(y:ys)) = last' y ys
69 last' _ (y:ys) = last' y ys
71 (is this necessarily an improvement)
78 drop n (x:xs) = drop (n-1) xs
80 Would like to pass n along unboxed.
83 To think about (Apr 94)
86 Main worry: duplicating code excessively. At the moment we duplicate
87 the entire binding group once at each recursive call. But there may
88 be a group of recursive calls which share a common set of evaluated
89 free variables, in which case the duplication is a plain waste.
91 Another thing we could consider adding is some unfold-threshold thing,
92 so that we'll only duplicate if the size of the group rhss isn't too
98 The ``level'' of a binder tells how many
99 recursive defns lexically enclose the binding
100 A recursive defn "encloses" its RHS, not its
103 letrec f = let g = ... in ...
108 Here, the level of @f@ is zero, the level of @g@ is one,
109 and the level of @h@ is zero (NB not one).
112 type LibCaseLevel = Int
114 topLevel :: LibCaseLevel
121 Int -- Bomb-out size for deciding if
122 -- potential liberatees are too big.
123 -- (passed in from cmd-line args)
125 LibCaseLevel -- Current level
127 (IdEnv LibCaseLevel) -- Binds all non-top-level in-scope Ids
128 -- (top-level and imported things have
131 (IdEnv CoreBind) -- Binds *only* recursively defined
132 -- Ids, to their own binding group,
133 -- and *only* in their own RHSs
135 [(Id,LibCaseLevel)] -- Each of these Ids was scrutinised by an
136 -- enclosing case expression, with the
137 -- specified number of enclosing
138 -- recursive bindings; furthermore,
139 -- the Id is bound at a lower level
140 -- than the case expression. The
141 -- order is insignificant; it's a bag
144 initEnv :: Int -> LibCaseEnv
145 initEnv bomb_size = LibCaseEnv bomb_size 0 emptyVarEnv emptyVarEnv []
147 bombOutSize (LibCaseEnv bomb_size _ _ _ _) = bomb_size
154 liberateCase :: DynFlags -> [CoreBind] -> IO [CoreBind]
155 liberateCase dflags binds
157 showPass dflags "Liberate case" ;
158 let { binds' = do_prog (initEnv opt_LiberateCaseThreshold) binds } ;
159 endPass dflags "Liberate case" Opt_D_verbose_core2core binds'
160 {- no specific flag for dumping -}
164 do_prog env (bind:binds) = bind' : do_prog env' binds
166 (env', bind') = libCaseBind env bind
173 libCaseBind :: LibCaseEnv -> CoreBind -> (LibCaseEnv, CoreBind)
175 libCaseBind env (NonRec binder rhs)
176 = (addBinders env [binder], NonRec binder (libCase env rhs))
178 libCaseBind env (Rec pairs)
179 = (env_body, Rec pairs')
181 (binders, rhss) = unzip pairs
183 env_body = addBinders env binders
185 pairs' = [(binder, libCase env_rhs rhs) | (binder,rhs) <- pairs]
187 env_rhs = if all rhs_small_enough rhss then extended_env else env
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!
193 extended_env = addRecBinds env [ (binder, libCase env_body rhs)
194 | (binder, rhs) <- pairs ]
196 rhs_small_enough rhs = couldBeSmallEnoughToInline lIBERATE_BOMB_SIZE rhs
197 lIBERATE_BOMB_SIZE = bombOutSize env
205 libCase :: LibCaseEnv
209 libCase env (Var v) = libCaseId env v
210 libCase env (Lit lit) = Lit lit
211 libCase env (Type ty) = Type ty
212 libCase env (App fun arg) = App (libCase env fun) (libCase env arg)
213 libCase env (Note note body) = Note note (libCase env body)
215 libCase env (Lam binder body)
216 = Lam binder (libCase (addBinders env [binder]) body)
218 libCase env (Let bind body)
219 = Let bind' (libCase env_body body)
221 (env_body, bind') = libCaseBind env bind
223 libCase env (Case scrut bndr alts)
224 = Case (libCase env scrut) bndr (map (libCaseAlt env_alts) alts)
226 env_alts = addBinders env_with_scrut [bndr]
227 env_with_scrut = case scrut of
228 Var scrut_var -> addScrutedVar env scrut_var
231 libCaseAlt env (con,args,rhs) = (con, args, libCase (addBinders env args) rhs)
237 libCaseId :: LibCaseEnv -> Id -> CoreExpr
239 | Just the_bind <- lookupRecId env v -- It's a use of a recursive thing
240 , notNull free_scruts -- with free vars scrutinised in RHS
241 = Let the_bind (Var v)
247 rec_id_level = lookupLevel env v
248 free_scruts = freeScruts env rec_id_level
256 addBinders :: LibCaseEnv -> [CoreBndr] -> LibCaseEnv
257 addBinders (LibCaseEnv bomb lvl lvl_env rec_env scruts) binders
258 = LibCaseEnv bomb lvl lvl_env' rec_env scruts
260 lvl_env' = extendVarEnvList lvl_env (binders `zip` repeat lvl)
262 addRecBinds :: LibCaseEnv -> [(Id,CoreExpr)] -> LibCaseEnv
263 addRecBinds (LibCaseEnv bomb lvl lvl_env rec_env scruts) pairs
264 = LibCaseEnv bomb lvl' lvl_env' rec_env' scruts
267 lvl_env' = extendVarEnvList lvl_env [(binder,lvl) | (binder,_) <- pairs]
268 rec_env' = extendVarEnvList rec_env [(binder, Rec pairs) | (binder,_) <- pairs]
270 addScrutedVar :: LibCaseEnv
271 -> Id -- This Id is being scrutinised by a case expression
274 addScrutedVar env@(LibCaseEnv bomb lvl lvl_env rec_env scruts) scrut_var
276 = LibCaseEnv bomb lvl lvl_env rec_env scruts'
277 -- Add to scruts iff the scrut_var is being scrutinised at
278 -- a deeper level than its defn
282 scruts' = (scrut_var, lvl) : scruts
283 bind_lvl = case lookupVarEnv lvl_env scrut_var of
287 lookupRecId :: LibCaseEnv -> Id -> Maybe CoreBind
288 lookupRecId (LibCaseEnv bomb lvl lvl_env rec_env scruts) id
289 = lookupVarEnv rec_env id
291 lookupLevel :: LibCaseEnv -> Id -> LibCaseLevel
292 lookupLevel (LibCaseEnv bomb lvl lvl_env rec_env scruts) id
293 = case lookupVarEnv lvl_env id of
297 freeScruts :: LibCaseEnv
298 -> LibCaseLevel -- Level of the recursive Id
299 -> [Id] -- Ids that are scrutinised between the binding
300 -- of the recursive Id and here
301 freeScruts (LibCaseEnv bomb lvl lvl_env rec_env scruts) rec_bind_lvl
302 = [v | (v,scrut_lvl) <- scruts, scrut_lvl > rec_bind_lvl]