Make letremoveunused work for recursive lets again.
[matthijs/master-project/cλash.git] / cλash / CLasH / Normalize.hs
1 {-# LANGUAGE PackageImports #-}
2 --
3 -- Functions to bring a Core expression in normal form. This module provides a
4 -- top level function "normalize", and defines the actual transformation passes that
5 -- are performed.
6 --
7 module CLasH.Normalize (getNormalized, normalizeExpr, splitNormalized) where
8
9 -- Standard modules
10 import Debug.Trace
11 import qualified Maybe
12 import qualified List
13 import qualified "transformers" Control.Monad.Trans as Trans
14 import qualified Control.Monad as Monad
15 import qualified Control.Monad.Trans.Writer as Writer
16 import qualified Data.Map as Map
17 import qualified Data.Monoid as Monoid
18 import Data.Accessor
19
20 -- GHC API
21 import CoreSyn
22 import qualified UniqSupply
23 import qualified CoreUtils
24 import qualified Type
25 import qualified TcType
26 import qualified Id
27 import qualified Var
28 import qualified VarSet
29 import qualified NameSet
30 import qualified CoreFVs
31 import qualified CoreUtils
32 import qualified MkCore
33 import qualified HscTypes
34 import Outputable ( showSDoc, ppr, nest )
35
36 -- Local imports
37 import CLasH.Normalize.NormalizeTypes
38 import CLasH.Translator.TranslatorTypes
39 import CLasH.Normalize.NormalizeTools
40 import CLasH.VHDL.VHDLTypes
41 import qualified CLasH.Utils as Utils
42 import CLasH.Utils.Core.CoreTools
43 import CLasH.Utils.Core.BinderTools
44 import CLasH.Utils.Pretty
45
46 --------------------------------
47 -- Start of transformations
48 --------------------------------
49
50 --------------------------------
51 -- η abstraction
52 --------------------------------
53 eta, etatop :: Transform
54 eta expr | is_fun expr && not (is_lam expr) = do
55   let arg_ty = (fst . Type.splitFunTy . CoreUtils.exprType) expr
56   id <- Trans.lift $ mkInternalVar "param" arg_ty
57   change (Lam id (App expr (Var id)))
58 -- Leave all other expressions unchanged
59 eta e = return e
60 etatop = notappargs ("eta", eta)
61
62 --------------------------------
63 -- β-reduction
64 --------------------------------
65 beta, betatop :: Transform
66 -- Substitute arg for x in expr
67 beta (App (Lam x expr) arg) = change $ substitute [(x, arg)] expr
68 -- Propagate the application into the let
69 beta (App (Let binds expr) arg) = change $ Let binds (App expr arg)
70 -- Propagate the application into each of the alternatives
71 beta (App (Case scrut b ty alts) arg) = change $ Case scrut b ty' alts'
72   where 
73     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (App expr arg))) alts
74     ty' = CoreUtils.applyTypeToArg ty arg
75 -- Leave all other expressions unchanged
76 beta expr = return expr
77 -- Perform this transform everywhere
78 betatop = everywhere ("beta", beta)
79
80 --------------------------------
81 -- Cast propagation
82 --------------------------------
83 -- Try to move casts as much downward as possible.
84 castprop, castproptop :: Transform
85 castprop (Cast (Let binds expr) ty) = change $ Let binds (Cast expr ty)
86 castprop expr@(Cast (Case scrut b _ alts) ty) = change (Case scrut b ty alts')
87   where
88     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (Cast expr ty))) alts
89 -- Leave all other expressions unchanged
90 castprop expr = return expr
91 -- Perform this transform everywhere
92 castproptop = everywhere ("castprop", castprop)
93
94 --------------------------------
95 -- Cast simplification. Mostly useful for state packing and unpacking, but
96 -- perhaps for others as well.
97 --------------------------------
98 castsimpl, castsimpltop :: Transform
99 castsimpl expr@(Cast val ty) = do
100   -- Don't extract values that are already simpl
101   local_var <- Trans.lift $ is_local_var val
102   -- Don't extract values that are not representable, to prevent loops with
103   -- inlinenonrep
104   repr <- isRepr val
105   if (not local_var) && repr
106     then do
107       -- Generate a binder for the expression
108       id <- Trans.lift $ mkBinderFor val "castval"
109       -- Extract the expression
110       change $ Let (NonRec id val) (Cast (Var id) ty)
111     else
112       return expr
113 -- Leave all other expressions unchanged
114 castsimpl expr = return expr
115 -- Perform this transform everywhere
116 castsimpltop = everywhere ("castsimpl", castsimpl)
117
118
119 --------------------------------
120 -- Lambda simplication
121 --------------------------------
122 -- Ensure that a lambda always evaluates to a let expressions or a simple
123 -- variable reference.
124 lambdasimpl, lambdasimpltop :: Transform
125 -- Don't simplify a lambda that evaluates to let, since this is already
126 -- normal form (and would cause infinite loops).
127 lambdasimpl expr@(Lam _ (Let _ _)) = return expr
128 -- Put the of a lambda in its own binding, but not when the expression is
129 -- already a local variable, or not representable (to prevent loops with
130 -- inlinenonrep).
131 lambdasimpl expr@(Lam bndr res) = do
132   repr <- isRepr res
133   local_var <- Trans.lift $ is_local_var res
134   if not local_var && repr
135     then do
136       id <- Trans.lift $ mkBinderFor res "res"
137       change $ Lam bndr (Let (NonRec id res) (Var id))
138     else
139       -- If the result is already a local var or not representable, don't
140       -- extract it.
141       return expr
142
143 -- Leave all other expressions unchanged
144 lambdasimpl expr = return expr
145 -- Perform this transform everywhere
146 lambdasimpltop = everywhere ("lambdasimpl", lambdasimpl)
147
148 --------------------------------
149 -- let derecursification
150 --------------------------------
151 letderec, letderectop :: Transform
152 letderec expr@(Let (Rec binds) res) = case liftable of
153   -- Nothing is liftable, just return
154   [] -> return expr
155   -- Something can be lifted, generate a new let expression
156   _ -> change $ mkNonRecLets liftable (Let (Rec nonliftable) res)
157   where
158     -- Make a list of all the binders bound in this recursive let
159     bndrs = map fst binds
160     -- See which bindings are liftable
161     (liftable, nonliftable) = List.partition canlift binds
162     -- Any expression that does not use any of the binders in this recursive let
163     -- can be lifted into a nonrec let. It can't use its own binder either,
164     -- since that would mean the binding is self-recursive and should be in a
165     -- single bind recursive let.
166     canlift (bndr, e) = not $ expr_uses_binders bndrs e
167 -- Leave all other expressions unchanged
168 letderec expr = return expr
169 -- Perform this transform everywhere
170 letderectop = everywhere ("letderec", letderec)
171
172 --------------------------------
173 -- let simplification
174 --------------------------------
175 letsimpl, letsimpltop :: Transform
176 -- Don't simplify a let that evaluates to another let, since this is already
177 -- normal form (and would cause infinite loops with letflat below).
178 letsimpl expr@(Let _ (Let _ _)) = return expr
179 -- Put the "in ..." value of a let in its own binding, but not when the
180 -- expression is already a local variable, or not representable (to prevent loops with inlinenonrep).
181 letsimpl expr@(Let binds res) = do
182   repr <- isRepr res
183   local_var <- Trans.lift $ is_local_var res
184   if not local_var && repr
185     then do
186       -- If the result is not a local var already (to prevent loops with
187       -- ourselves), extract it.
188       id <- Trans.lift $ mkBinderFor res "foo"
189       change $ Let binds (Let (NonRec id  res) (Var id))
190     else
191       -- If the result is already a local var, don't extract it.
192       return expr
193
194 -- Leave all other expressions unchanged
195 letsimpl expr = return expr
196 -- Perform this transform everywhere
197 letsimpltop = everywhere ("letsimpl", letsimpl)
198
199 --------------------------------
200 -- let flattening
201 --------------------------------
202 -- Takes a let that binds another let, and turns that into two nested lets.
203 -- e.g., from:
204 -- let b = (let b' = expr' in res') in res
205 -- to:
206 -- let b' = expr' in (let b = res' in res)
207 letflat, letflattop :: Transform
208 -- Turn a nonrec let that binds a let into two nested lets.
209 letflat (Let (NonRec b (Let binds  res')) res) = 
210   change $ Let binds (Let (NonRec b res') res)
211 letflat (Let (Rec binds) expr) = do
212   -- Flatten each binding.
213   binds' <- Utils.concatM $ Monad.mapM flatbind binds
214   -- Return the new let. We don't use change here, since possibly nothing has
215   -- changed. If anything has changed, flatbind has already flagged that
216   -- change.
217   return $ Let (Rec binds') expr
218   where
219     -- Turns a binding of a let into a multiple bindings, or any other binding
220     -- into a list with just that binding
221     flatbind :: (CoreBndr, CoreExpr) -> TransformMonad [(CoreBndr, CoreExpr)]
222     flatbind (b, Let (Rec binds) expr) = change ((b, expr):binds)
223     flatbind (b, expr) = return [(b, expr)]
224 -- Leave all other expressions unchanged
225 letflat expr = return expr
226 -- Perform this transform everywhere
227 letflattop = everywhere ("letflat", letflat)
228
229 --------------------------------
230 -- empty let removal
231 --------------------------------
232 -- Remove empty (recursive) lets
233 letremove, letremovetop :: Transform
234 letremove (Let (Rec []) res) = change $ res
235 -- Leave all other expressions unchanged
236 letremove expr = return expr
237 -- Perform this transform everywhere
238 letremovetop = everywhere ("letremove", letremove)
239
240 --------------------------------
241 -- Simple let binding removal
242 --------------------------------
243 -- Remove a = b bindings from let expressions everywhere
244 letremovesimpletop :: Transform
245 letremovesimpletop = everywhere ("letremovesimple", inlinebind (\(b, e) -> Trans.lift $ is_local_var e))
246
247 --------------------------------
248 -- Unused let binding removal
249 --------------------------------
250 letremoveunused, letremoveunusedtop :: Transform
251 letremoveunused expr@(Let (NonRec b bound) res) = do
252   let used = expr_uses_binders [b] res
253   if used
254     then return expr
255     else change res
256 letremoveunused expr@(Let (Rec binds) res) = do
257   -- Filter out all unused binds.
258   let binds' = filter dobind binds
259   -- Only set the changed flag if binds got removed
260   changeif (length binds' /= length binds) (Let (Rec binds') res)
261     where
262       bound_exprs = map snd binds
263       -- For each bind check if the bind is used by res or any of the bound
264       -- expressions
265       dobind (bndr, _) = any (expr_uses_binders [bndr]) (res:bound_exprs)
266 -- Leave all other expressions unchanged
267 letremoveunused expr = return expr
268 letremoveunusedtop = everywhere ("letremoveunused", letremoveunused)
269
270 --------------------------------
271 -- Identical let binding merging
272 --------------------------------
273 -- Merge two bindings in a let if they are identical 
274 -- TODO: We would very much like to use GHC's CSE module for this, but that
275 -- doesn't track if something changed or not, so we can't use it properly.
276 letmerge, letmergetop :: Transform
277 letmerge expr@(Let _ _) = do
278   let (binds, res) = flattenLets expr
279   binds' <- domerge binds
280   return $ mkNonRecLets binds' res
281   where
282     domerge :: [(CoreBndr, CoreExpr)] -> TransformMonad [(CoreBndr, CoreExpr)]
283     domerge [] = return []
284     domerge (e:es) = do 
285       es' <- mapM (mergebinds e) es
286       es'' <- domerge es'
287       return (e:es'')
288
289     -- Uses the second bind to simplify the second bind, if applicable.
290     mergebinds :: (CoreBndr, CoreExpr) -> (CoreBndr, CoreExpr) -> TransformMonad (CoreBndr, CoreExpr)
291     mergebinds (b1, e1) (b2, e2)
292       -- Identical expressions? Replace the second binding with a reference to
293       -- the first binder.
294       | CoreUtils.cheapEqExpr e1 e2 = change $ (b2, Var b1)
295       -- Different expressions? Don't change
296       | otherwise = return (b2, e2)
297 -- Leave all other expressions unchanged
298 letmerge expr = return expr
299 letmergetop = everywhere ("letmerge", letmerge)
300     
301 --------------------------------
302 -- Function inlining
303 --------------------------------
304 -- Remove a = B bindings, with B :: a -> b, or B :: forall x . T, from let
305 -- expressions everywhere. This means that any value that still needs to be
306 -- applied to something else (polymorphic values need to be applied to a
307 -- Type) will be inlined, and will eventually be applied to all their
308 -- arguments.
309 --
310 -- This is a tricky function, which is prone to create loops in the
311 -- transformations. To fix this, we make sure that no transformation will
312 -- create a new let binding with a function type. These other transformations
313 -- will just not work on those function-typed values at first, but the other
314 -- transformations (in particular β-reduction) should make sure that the type
315 -- of those values eventually becomes primitive.
316 inlinenonreptop :: Transform
317 inlinenonreptop = everywhere ("inlinenonrep", inlinebind ((Monad.liftM not) . isRepr . snd))
318
319 --------------------------------
320 -- Scrutinee simplification
321 --------------------------------
322 scrutsimpl,scrutsimpltop :: Transform
323 -- Don't touch scrutinees that are already simple
324 scrutsimpl expr@(Case (Var _) _ _ _) = return expr
325 -- Replace all other cases with a let that binds the scrutinee and a new
326 -- simple scrutinee, but only when the scrutinee is representable (to prevent
327 -- loops with inlinenonrep, though I don't think a non-representable scrutinee
328 -- will be supported anyway...) 
329 scrutsimpl expr@(Case scrut b ty alts) = do
330   repr <- isRepr scrut
331   if repr
332     then do
333       id <- Trans.lift $ mkBinderFor scrut "scrut"
334       change $ Let (NonRec id scrut) (Case (Var id) b ty alts)
335     else
336       return expr
337 -- Leave all other expressions unchanged
338 scrutsimpl expr = return expr
339 -- Perform this transform everywhere
340 scrutsimpltop = everywhere ("scrutsimpl", scrutsimpl)
341
342 --------------------------------
343 -- Case binder wildening
344 --------------------------------
345 casesimpl, casesimpltop :: Transform
346 -- This is already a selector case (or, if x does not appear in bndrs, a very
347 -- simple case statement that will be removed by caseremove below). Just leave
348 -- it be.
349 casesimpl expr@(Case scrut b ty [(con, bndrs, Var x)]) = return expr
350 -- Make sure that all case alternatives have only wild binders and simple
351 -- expressions.
352 -- This is done by creating a new let binding for each non-wild binder, which
353 -- is bound to a new simple selector case statement and for each complex
354 -- expression. We do this only for representable types, to prevent loops with
355 -- inlinenonrep.
356 casesimpl expr@(Case scrut b ty alts) = do
357   (bindingss, alts') <- (Monad.liftM unzip) $ mapM doalt alts
358   let bindings = concat bindingss
359   -- Replace the case with a let with bindings and a case
360   let newlet = mkNonRecLets bindings (Case scrut b ty alts')
361   -- If there are no non-wild binders, or this case is already a simple
362   -- selector (i.e., a single alt with exactly one binding), already a simple
363   -- selector altan no bindings (i.e., no wild binders in the original case),
364   -- don't change anything, otherwise, replace the case.
365   if null bindings then return expr else change newlet 
366   where
367   -- Generate a single wild binder, since they are all the same
368   wild = MkCore.mkWildBinder
369   -- Wilden the binders of one alt, producing a list of bindings as a
370   -- sideeffect.
371   doalt :: CoreAlt -> TransformMonad ([(CoreBndr, CoreExpr)], CoreAlt)
372   doalt (con, bndrs, expr) = do
373     -- Make each binder wild, if possible
374     bndrs_res <- Monad.zipWithM dobndr bndrs [0..]
375     let (newbndrs, bindings_maybe) = unzip bndrs_res
376     -- Extract a complex expression, if possible. For this we check if any of
377     -- the new list of bndrs are used by expr. We can't use free_vars here,
378     -- since that looks at the old bndrs.
379     let uses_bndrs = not $ VarSet.isEmptyVarSet $ CoreFVs.exprSomeFreeVars (`elem` newbndrs) $ expr
380     (exprbinding_maybe, expr') <- doexpr expr uses_bndrs
381     -- Create a new alternative
382     let newalt = (con, newbndrs, expr')
383     let bindings = Maybe.catMaybes (bindings_maybe ++ [exprbinding_maybe])
384     return (bindings, newalt)
385     where
386       -- Make wild alternatives for each binder
387       wildbndrs = map (\bndr -> MkCore.mkWildBinder (Id.idType bndr)) bndrs
388       -- A set of all the binders that are used by the expression
389       free_vars = CoreFVs.exprSomeFreeVars (`elem` bndrs) expr
390       -- Look at the ith binder in the case alternative. Return a new binder
391       -- for it (either the same one, or a wild one) and optionally a let
392       -- binding containing a case expression.
393       dobndr :: CoreBndr -> Int -> TransformMonad (CoreBndr, Maybe (CoreBndr, CoreExpr))
394       dobndr b i = do
395         repr <- isRepr (Var b)
396         -- Is b wild (e.g., not a free var of expr. Since b is only in scope
397         -- in expr, this means that b is unused if expr does not use it.)
398         let wild = not (VarSet.elemVarSet b free_vars)
399         -- Create a new binding for any representable binder that is not
400         -- already wild and is representable (to prevent loops with
401         -- inlinenonrep).
402         if (not wild) && repr
403           then do
404             -- Create on new binder that will actually capture a value in this
405             -- case statement, and return it.
406             let bty = (Id.idType b)
407             id <- Trans.lift $ mkInternalVar "sel" bty
408             let binders = take i wildbndrs ++ [id] ++ drop (i+1) wildbndrs
409             let caseexpr = Case scrut b bty [(con, binders, Var id)]
410             return (wildbndrs!!i, Just (b, caseexpr))
411           else 
412             -- Just leave the original binder in place, and don't generate an
413             -- extra selector case.
414             return (b, Nothing)
415       -- Process the expression of a case alternative. Accepts an expression
416       -- and whether this expression uses any of the binders in the
417       -- alternative. Returns an optional new binding and a new expression.
418       doexpr :: CoreExpr -> Bool -> TransformMonad (Maybe (CoreBndr, CoreExpr), CoreExpr)
419       doexpr expr uses_bndrs = do
420         local_var <- Trans.lift $ is_local_var expr
421         repr <- isRepr expr
422         -- Extract any expressions that do not use any binders from this
423         -- alternative, is not a local var already and is representable (to
424         -- prevent loops with inlinenonrep).
425         if (not uses_bndrs) && (not local_var) && repr
426           then do
427             id <- Trans.lift $ mkBinderFor expr "caseval"
428             -- We don't flag a change here, since casevalsimpl will do that above
429             -- based on Just we return here.
430             return $ (Just (id, expr), Var id)
431           else
432             -- Don't simplify anything else
433             return (Nothing, expr)
434 -- Leave all other expressions unchanged
435 casesimpl expr = return expr
436 -- Perform this transform everywhere
437 casesimpltop = everywhere ("casesimpl", casesimpl)
438
439 --------------------------------
440 -- Case removal
441 --------------------------------
442 -- Remove case statements that have only a single alternative and only wild
443 -- binders.
444 caseremove, caseremovetop :: Transform
445 -- Replace a useless case by the value of its single alternative
446 caseremove (Case scrut b ty [(con, bndrs, expr)]) | not usesvars = change expr
447     -- Find if any of the binders are used by expr
448     where usesvars = (not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` bndrs))) expr
449 -- Leave all other expressions unchanged
450 caseremove expr = return expr
451 -- Perform this transform everywhere
452 caseremovetop = everywhere ("caseremove", caseremove)
453
454 --------------------------------
455 -- Argument extraction
456 --------------------------------
457 -- Make sure that all arguments of a representable type are simple variables.
458 appsimpl, appsimpltop :: Transform
459 -- Simplify all representable arguments. Do this by introducing a new Let
460 -- that binds the argument and passing the new binder in the application.
461 appsimpl expr@(App f arg) = do
462   -- Check runtime representability
463   repr <- isRepr arg
464   local_var <- Trans.lift $ is_local_var arg
465   if repr && not local_var
466     then do -- Extract representable arguments
467       id <- Trans.lift $ mkBinderFor arg "arg"
468       change $ Let (NonRec id arg) (App f (Var id))
469     else -- Leave non-representable arguments unchanged
470       return expr
471 -- Leave all other expressions unchanged
472 appsimpl expr = return expr
473 -- Perform this transform everywhere
474 appsimpltop = everywhere ("appsimpl", appsimpl)
475
476 --------------------------------
477 -- Function-typed argument propagation
478 --------------------------------
479 -- Remove all applications to function-typed arguments, by duplication the
480 -- function called with the function-typed parameter replaced by the free
481 -- variables of the argument passed in.
482 argprop, argproptop :: Transform
483 -- Transform any application of a named function (i.e., skip applications of
484 -- lambda's). Also skip applications that have arguments with free type
485 -- variables, since we can't inline those.
486 argprop expr@(App _ _) | is_var fexpr = do
487   -- Find the body of the function called
488   body_maybe <- Trans.lift $ getGlobalBind f
489   case body_maybe of
490     Just body -> do
491       -- Process each of the arguments in turn
492       (args', changed) <- Writer.listen $ mapM doarg args
493       -- See if any of the arguments changed
494       case Monoid.getAny changed of
495         True -> do
496           let (newargs', newparams', oldargs) = unzip3 args'
497           let newargs = concat newargs'
498           let newparams = concat newparams'
499           -- Create a new body that consists of a lambda for all new arguments and
500           -- the old body applied to some arguments.
501           let newbody = MkCore.mkCoreLams newparams (MkCore.mkCoreApps body oldargs)
502           -- Create a new function with the same name but a new body
503           newf <- Trans.lift $ mkFunction f newbody
504           -- Replace the original application with one of the new function to the
505           -- new arguments.
506           change $ MkCore.mkCoreApps (Var newf) newargs
507         False ->
508           -- Don't change the expression if none of the arguments changed
509           return expr
510       
511     -- If we don't have a body for the function called, leave it unchanged (it
512     -- should be a primitive function then).
513     Nothing -> return expr
514   where
515     -- Find the function called and the arguments
516     (fexpr, args) = collectArgs expr
517     Var f = fexpr
518
519     -- Process a single argument and return (args, bndrs, arg), where args are
520     -- the arguments to replace the given argument in the original
521     -- application, bndrs are the binders to include in the top-level lambda
522     -- in the new function body, and arg is the argument to apply to the old
523     -- function body.
524     doarg :: CoreExpr -> TransformMonad ([CoreExpr], [CoreBndr], CoreExpr)
525     doarg arg = do
526       repr <- isRepr arg
527       bndrs <- Trans.lift getGlobalBinders
528       let interesting var = Var.isLocalVar var && (not $ var `elem` bndrs)
529       if not repr && not (is_var arg && interesting (exprToVar arg)) && not (has_free_tyvars arg) 
530         then do
531           -- Propagate all complex arguments that are not representable, but not
532           -- arguments with free type variables (since those would require types
533           -- not known yet, which will always be known eventually).
534           -- Find interesting free variables, each of which should be passed to
535           -- the new function instead of the original function argument.
536           -- 
537           -- Interesting vars are those that are local, but not available from the
538           -- top level scope (functions from this module are defined as local, but
539           -- they're not local to this function, so we can freely move references
540           -- to them into another function).
541           let free_vars = VarSet.varSetElems $ CoreFVs.exprSomeFreeVars interesting arg
542           -- Mark the current expression as changed
543           setChanged
544           return (map Var free_vars, free_vars, arg)
545         else do
546           -- Representable types will not be propagated, and arguments with free
547           -- type variables will be propagated later.
548           -- TODO: preserve original naming?
549           id <- Trans.lift $ mkBinderFor arg "param"
550           -- Just pass the original argument to the new function, which binds it
551           -- to a new id and just pass that new id to the old function body.
552           return ([arg], [id], mkReferenceTo id) 
553 -- Leave all other expressions unchanged
554 argprop expr = return expr
555 -- Perform this transform everywhere
556 argproptop = everywhere ("argprop", argprop)
557
558 --------------------------------
559 -- Function-typed argument extraction
560 --------------------------------
561 -- This transform takes any function-typed argument that cannot be propagated
562 -- (because the function that is applied to it is a builtin function), and
563 -- puts it in a brand new top level binder. This allows us to for example
564 -- apply map to a lambda expression This will not conflict with inlinenonrep,
565 -- since that only inlines local let bindings, not top level bindings.
566 funextract, funextracttop :: Transform
567 funextract expr@(App _ _) | is_var fexpr = do
568   body_maybe <- Trans.lift $ getGlobalBind f
569   case body_maybe of
570     -- We don't have a function body for f, so we can perform this transform.
571     Nothing -> do
572       -- Find the new arguments
573       args' <- mapM doarg args
574       -- And update the arguments. We use return instead of changed, so the
575       -- changed flag doesn't get set if none of the args got changed.
576       return $ MkCore.mkCoreApps fexpr args'
577     -- We have a function body for f, leave this application to funprop
578     Just _ -> return expr
579   where
580     -- Find the function called and the arguments
581     (fexpr, args) = collectArgs expr
582     Var f = fexpr
583     -- Change any arguments that have a function type, but are not simple yet
584     -- (ie, a variable or application). This means to create a new function
585     -- for map (\f -> ...) b, but not for map (foo a) b.
586     --
587     -- We could use is_applicable here instead of is_fun, but I think
588     -- arguments to functions could only have forall typing when existential
589     -- typing is enabled. Not sure, though.
590     doarg arg | not (is_simple arg) && is_fun arg = do
591       -- Create a new top level binding that binds the argument. Its body will
592       -- be extended with lambda expressions, to take any free variables used
593       -- by the argument expression.
594       let free_vars = VarSet.varSetElems $ CoreFVs.exprFreeVars arg
595       let body = MkCore.mkCoreLams free_vars arg
596       id <- Trans.lift $ mkBinderFor body "fun"
597       Trans.lift $ addGlobalBind id body
598       -- Replace the argument with a reference to the new function, applied to
599       -- all vars it uses.
600       change $ MkCore.mkCoreApps (Var id) (map Var free_vars)
601     -- Leave all other arguments untouched
602     doarg arg = return arg
603
604 -- Leave all other expressions unchanged
605 funextract expr = return expr
606 -- Perform this transform everywhere
607 funextracttop = everywhere ("funextract", funextract)
608
609 --------------------------------
610 -- End of transformations
611 --------------------------------
612
613
614
615
616 -- What transforms to run?
617 transforms = [argproptop, funextracttop, etatop, betatop, castproptop, letremovesimpletop, letderectop, letremovetop, letsimpltop, letflattop, scrutsimpltop, casesimpltop, caseremovetop, inlinenonreptop, appsimpltop, letmergetop, letremoveunusedtop, castsimpltop, lambdasimpltop]
618
619 -- | Returns the normalized version of the given function.
620 getNormalized ::
621   CoreBndr -- ^ The function to get
622   -> TranslatorSession CoreExpr -- The normalized function body
623
624 getNormalized bndr = Utils.makeCached bndr tsNormalized $ do
625   if is_poly (Var bndr)
626     then
627       -- This should really only happen at the top level... TODO: Give
628       -- a different error if this happens down in the recursion.
629       error $ "\nNormalize.normalizeBind: Function " ++ show bndr ++ " is polymorphic, can't normalize"
630     else do
631       expr <- getBinding bndr
632       normalizeExpr (show bndr) expr
633
634 -- | Normalize an expression
635 normalizeExpr ::
636   String -- ^ What are we normalizing? For debug output only.
637   -> CoreSyn.CoreExpr -- ^ The expression to normalize 
638   -> TranslatorSession CoreSyn.CoreExpr -- ^ The normalized expression
639
640 normalizeExpr what expr = do
641       -- Normalize this expression
642       trace (what ++ " before normalization:\n\n" ++ showSDoc ( ppr expr ) ++ "\n") $ return ()
643       expr' <- dotransforms transforms expr
644       trace ("\n" ++ what ++ " after normalization:\n\n" ++ showSDoc ( ppr expr')) $ return ()
645       return expr'
646
647 -- | Get the value that is bound to the given binder at top level. Fails when
648 --   there is no such binding.
649 getBinding ::
650   CoreBndr -- ^ The binder to get the expression for
651   -> TranslatorSession CoreExpr -- ^ The value bound to the binder
652
653 getBinding bndr = Utils.makeCached bndr tsBindings $ do
654   -- If the binding isn't in the "cache" (bindings map), then we can't create
655   -- it out of thin air, so return an error.
656   error $ "Normalize.getBinding: Unknown function requested: " ++ show bndr
657
658 -- | Split a normalized expression into the argument binders, top level
659 --   bindings and the result binder.
660 splitNormalized ::
661   CoreExpr -- ^ The normalized expression
662   -> ([CoreBndr], [Binding], CoreBndr)
663 splitNormalized expr = (args, binds, res)
664   where
665     (args, letexpr) = CoreSyn.collectBinders expr
666     (binds, resexpr) = flattenLets letexpr
667     res = case resexpr of 
668       (Var x) -> x
669       _ -> error $ "Normalize.splitNormalized: Not in normal form: " ++ pprString expr ++ "\n"