Make letflat work with non-recursive lets.
[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 -- let derecursification
120 --------------------------------
121 letderec, letderectop :: Transform
122 letderec expr@(Let (Rec binds) res) = case liftable of
123   -- Nothing is liftable, just return
124   [] -> return expr
125   -- Something can be lifted, generate a new let expression
126   _ -> change $ MkCore.mkCoreLets newbinds res
127   where
128     -- Make a list of all the binders bound in this recursive let
129     bndrs = map fst binds
130     -- See which bindings are liftable
131     (liftable, nonliftable) = List.partition canlift binds
132     -- Create nonrec bindings for each liftable binding and a single recursive
133     -- binding for all others
134     newbinds = (map (uncurry NonRec) liftable) ++ [Rec nonliftable]
135     -- Any expression that does not use any of the binders in this recursive let
136     -- can be lifted into a nonrec let. It can't use its own binder either,
137     -- since that would mean the binding is self-recursive and should be in a
138     -- single bind recursive let.
139     canlift (bndr, e) = not $ expr_uses_binders bndrs e
140 -- Leave all other expressions unchanged
141 letderec expr = return expr
142 -- Perform this transform everywhere
143 letderectop = everywhere ("letderec", letderec)
144
145 --------------------------------
146 -- let simplification
147 --------------------------------
148 letsimpl, letsimpltop :: Transform
149 -- Put the "in ..." value of a let in its own binding, but not when the
150 -- expression is already a local variable, or not representable (to prevent loops with inlinenonrep).
151 letsimpl expr@(Let binds res) = do
152   repr <- isRepr res
153   local_var <- Trans.lift $ is_local_var res
154   if not local_var && repr
155     then do
156       -- If the result is not a local var already (to prevent loops with
157       -- ourselves), extract it.
158       id <- Trans.lift $ mkBinderFor res "foo"
159       change $ Let binds (Let (NonRec id  res) (Var id))
160     else
161       -- If the result is already a local var, don't extract it.
162       return expr
163
164 -- Leave all other expressions unchanged
165 letsimpl expr = return expr
166 -- Perform this transform everywhere
167 letsimpltop = everywhere ("letsimpl", letsimpl)
168
169 --------------------------------
170 -- let flattening
171 --------------------------------
172 -- Takes a let that binds another let, and turns that into two nested lets.
173 -- e.g., from:
174 -- let b = (let b' = expr' in res') in res
175 -- to:
176 -- let b' = expr' in (let b = res' in res)
177 letflat, letflattop :: Transform
178 letflat (Let (NonRec b (Let (NonRec b' expr')  res')) res) = 
179   change $ Let (NonRec b' expr') (Let (NonRec b res') res)
180 -- Leave all other expressions unchanged
181 letflat expr = return expr
182 -- Perform this transform everywhere
183 letflattop = everywhere ("letflat", letflat)
184
185 --------------------------------
186 -- Simple let binding removal
187 --------------------------------
188 -- Remove a = b bindings from let expressions everywhere
189 letremovetop :: Transform
190 letremovetop = everywhere ("letremove", inlinebind (\(b, e) -> Trans.lift $ is_local_var e))
191
192 --------------------------------
193 -- Unused let binding removal
194 --------------------------------
195 letremoveunused, letremoveunusedtop :: Transform
196 letremoveunused expr@(Let (Rec binds) res) = do
197   -- Filter out all unused binds.
198   let binds' = filter dobind binds
199   -- Only set the changed flag if binds got removed
200   changeif (length binds' /= length binds) (Let (Rec binds') res)
201     where
202       bound_exprs = map snd binds
203       -- For each bind check if the bind is used by res or any of the bound
204       -- expressions
205       dobind (bndr, _) = any (expr_uses_binders [bndr]) (res:bound_exprs)
206 -- Leave all other expressions unchanged
207 letremoveunused expr = return expr
208 letremoveunusedtop = everywhere ("letremoveunused", letremoveunused)
209
210 --------------------------------
211 -- Identical let binding merging
212 --------------------------------
213 -- Merge two bindings in a let if they are identical 
214 -- TODO: We would very much like to use GHC's CSE module for this, but that
215 -- doesn't track if something changed or not, so we can't use it properly.
216 letmerge, letmergetop :: Transform
217 letmerge expr@(Let (Rec binds) res) = do
218   binds' <- domerge binds
219   return (Let (Rec binds') res)
220   where
221     domerge :: [(CoreBndr, CoreExpr)] -> TransformMonad [(CoreBndr, CoreExpr)]
222     domerge [] = return []
223     domerge (e:es) = do 
224       es' <- mapM (mergebinds e) es
225       es'' <- domerge es'
226       return (e:es'')
227
228     -- Uses the second bind to simplify the second bind, if applicable.
229     mergebinds :: (CoreBndr, CoreExpr) -> (CoreBndr, CoreExpr) -> TransformMonad (CoreBndr, CoreExpr)
230     mergebinds (b1, e1) (b2, e2)
231       -- Identical expressions? Replace the second binding with a reference to
232       -- the first binder.
233       | CoreUtils.cheapEqExpr e1 e2 = change $ (b2, Var b1)
234       -- Different expressions? Don't change
235       | otherwise = return (b2, e2)
236 -- Leave all other expressions unchanged
237 letmerge expr = return expr
238 letmergetop = everywhere ("letmerge", letmerge)
239     
240 --------------------------------
241 -- Function inlining
242 --------------------------------
243 -- Remove a = B bindings, with B :: a -> b, or B :: forall x . T, from let
244 -- expressions everywhere. This means that any value that still needs to be
245 -- applied to something else (polymorphic values need to be applied to a
246 -- Type) will be inlined, and will eventually be applied to all their
247 -- arguments.
248 --
249 -- This is a tricky function, which is prone to create loops in the
250 -- transformations. To fix this, we make sure that no transformation will
251 -- create a new let binding with a function type. These other transformations
252 -- will just not work on those function-typed values at first, but the other
253 -- transformations (in particular β-reduction) should make sure that the type
254 -- of those values eventually becomes primitive.
255 inlinenonreptop :: Transform
256 inlinenonreptop = everywhere ("inlinenonrep", inlinebind ((Monad.liftM not) . isRepr . snd))
257
258 --------------------------------
259 -- Scrutinee simplification
260 --------------------------------
261 scrutsimpl,scrutsimpltop :: Transform
262 -- Don't touch scrutinees that are already simple
263 scrutsimpl expr@(Case (Var _) _ _ _) = return expr
264 -- Replace all other cases with a let that binds the scrutinee and a new
265 -- simple scrutinee, but only when the scrutinee is representable (to prevent
266 -- loops with inlinenonrep, though I don't think a non-representable scrutinee
267 -- will be supported anyway...) 
268 scrutsimpl expr@(Case scrut b ty alts) = do
269   repr <- isRepr scrut
270   if repr
271     then do
272       id <- Trans.lift $ mkBinderFor scrut "scrut"
273       change $ Let (NonRec id scrut) (Case (Var id) b ty alts)
274     else
275       return expr
276 -- Leave all other expressions unchanged
277 scrutsimpl expr = return expr
278 -- Perform this transform everywhere
279 scrutsimpltop = everywhere ("scrutsimpl", scrutsimpl)
280
281 --------------------------------
282 -- Case binder wildening
283 --------------------------------
284 casesimpl, casesimpltop :: Transform
285 -- This is already a selector case (or, if x does not appear in bndrs, a very
286 -- simple case statement that will be removed by caseremove below). Just leave
287 -- it be.
288 casesimpl expr@(Case scrut b ty [(con, bndrs, Var x)]) = return expr
289 -- Make sure that all case alternatives have only wild binders and simple
290 -- expressions.
291 -- This is done by creating a new let binding for each non-wild binder, which
292 -- is bound to a new simple selector case statement and for each complex
293 -- expression. We do this only for representable types, to prevent loops with
294 -- inlinenonrep.
295 casesimpl expr@(Case scrut b ty alts) = do
296   (bindingss, alts') <- (Monad.liftM unzip) $ mapM doalt alts
297   let bindings = concat bindingss
298   -- Replace the case with a let with bindings and a case
299   let newlet = (Let (Rec bindings) (Case scrut b ty alts'))
300   -- If there are no non-wild binders, or this case is already a simple
301   -- selector (i.e., a single alt with exactly one binding), already a simple
302   -- selector altan no bindings (i.e., no wild binders in the original case),
303   -- don't change anything, otherwise, replace the case.
304   if null bindings then return expr else change newlet 
305   where
306   -- Generate a single wild binder, since they are all the same
307   wild = MkCore.mkWildBinder
308   -- Wilden the binders of one alt, producing a list of bindings as a
309   -- sideeffect.
310   doalt :: CoreAlt -> TransformMonad ([(CoreBndr, CoreExpr)], CoreAlt)
311   doalt (con, bndrs, expr) = do
312     -- Make each binder wild, if possible
313     bndrs_res <- Monad.zipWithM dobndr bndrs [0..]
314     let (newbndrs, bindings_maybe) = unzip bndrs_res
315     -- Extract a complex expression, if possible. For this we check if any of
316     -- the new list of bndrs are used by expr. We can't use free_vars here,
317     -- since that looks at the old bndrs.
318     let uses_bndrs = not $ VarSet.isEmptyVarSet $ CoreFVs.exprSomeFreeVars (`elem` newbndrs) $ expr
319     (exprbinding_maybe, expr') <- doexpr expr uses_bndrs
320     -- Create a new alternative
321     let newalt = (con, newbndrs, expr')
322     let bindings = Maybe.catMaybes (exprbinding_maybe : bindings_maybe)
323     return (bindings, newalt)
324     where
325       -- Make wild alternatives for each binder
326       wildbndrs = map (\bndr -> MkCore.mkWildBinder (Id.idType bndr)) bndrs
327       -- A set of all the binders that are used by the expression
328       free_vars = CoreFVs.exprSomeFreeVars (`elem` bndrs) expr
329       -- Look at the ith binder in the case alternative. Return a new binder
330       -- for it (either the same one, or a wild one) and optionally a let
331       -- binding containing a case expression.
332       dobndr :: CoreBndr -> Int -> TransformMonad (CoreBndr, Maybe (CoreBndr, CoreExpr))
333       dobndr b i = do
334         repr <- isRepr (Var b)
335         -- Is b wild (e.g., not a free var of expr. Since b is only in scope
336         -- in expr, this means that b is unused if expr does not use it.)
337         let wild = not (VarSet.elemVarSet b free_vars)
338         -- Create a new binding for any representable binder that is not
339         -- already wild and is representable (to prevent loops with
340         -- inlinenonrep).
341         if (not wild) && repr
342           then do
343             -- Create on new binder that will actually capture a value in this
344             -- case statement, and return it.
345             let bty = (Id.idType b)
346             id <- Trans.lift $ mkInternalVar "sel" bty
347             let binders = take i wildbndrs ++ [id] ++ drop (i+1) wildbndrs
348             let caseexpr = Case scrut b bty [(con, binders, Var id)]
349             return (wildbndrs!!i, Just (b, caseexpr))
350           else 
351             -- Just leave the original binder in place, and don't generate an
352             -- extra selector case.
353             return (b, Nothing)
354       -- Process the expression of a case alternative. Accepts an expression
355       -- and whether this expression uses any of the binders in the
356       -- alternative. Returns an optional new binding and a new expression.
357       doexpr :: CoreExpr -> Bool -> TransformMonad (Maybe (CoreBndr, CoreExpr), CoreExpr)
358       doexpr expr uses_bndrs = do
359         local_var <- Trans.lift $ is_local_var expr
360         repr <- isRepr expr
361         -- Extract any expressions that do not use any binders from this
362         -- alternative, is not a local var already and is representable (to
363         -- prevent loops with inlinenonrep).
364         if (not uses_bndrs) && (not local_var) && repr
365           then do
366             id <- Trans.lift $ mkBinderFor expr "caseval"
367             -- We don't flag a change here, since casevalsimpl will do that above
368             -- based on Just we return here.
369             return $ (Just (id, expr), Var id)
370           else
371             -- Don't simplify anything else
372             return (Nothing, expr)
373 -- Leave all other expressions unchanged
374 casesimpl expr = return expr
375 -- Perform this transform everywhere
376 casesimpltop = everywhere ("casesimpl", casesimpl)
377
378 --------------------------------
379 -- Case removal
380 --------------------------------
381 -- Remove case statements that have only a single alternative and only wild
382 -- binders.
383 caseremove, caseremovetop :: Transform
384 -- Replace a useless case by the value of its single alternative
385 caseremove (Case scrut b ty [(con, bndrs, expr)]) | not usesvars = change expr
386     -- Find if any of the binders are used by expr
387     where usesvars = (not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` bndrs))) expr
388 -- Leave all other expressions unchanged
389 caseremove expr = return expr
390 -- Perform this transform everywhere
391 caseremovetop = everywhere ("caseremove", caseremove)
392
393 --------------------------------
394 -- Argument extraction
395 --------------------------------
396 -- Make sure that all arguments of a representable type are simple variables.
397 appsimpl, appsimpltop :: Transform
398 -- Simplify all representable arguments. Do this by introducing a new Let
399 -- that binds the argument and passing the new binder in the application.
400 appsimpl expr@(App f arg) = do
401   -- Check runtime representability
402   repr <- isRepr arg
403   local_var <- Trans.lift $ is_local_var arg
404   if repr && not local_var
405     then do -- Extract representable arguments
406       id <- Trans.lift $ mkBinderFor arg "arg"
407       change $ Let (NonRec id arg) (App f (Var id))
408     else -- Leave non-representable arguments unchanged
409       return expr
410 -- Leave all other expressions unchanged
411 appsimpl expr = return expr
412 -- Perform this transform everywhere
413 appsimpltop = everywhere ("appsimpl", appsimpl)
414
415 --------------------------------
416 -- Function-typed argument propagation
417 --------------------------------
418 -- Remove all applications to function-typed arguments, by duplication the
419 -- function called with the function-typed parameter replaced by the free
420 -- variables of the argument passed in.
421 argprop, argproptop :: Transform
422 -- Transform any application of a named function (i.e., skip applications of
423 -- lambda's). Also skip applications that have arguments with free type
424 -- variables, since we can't inline those.
425 argprop expr@(App _ _) | is_var fexpr = do
426   -- Find the body of the function called
427   body_maybe <- Trans.lift $ getGlobalBind f
428   case body_maybe of
429     Just body -> do
430       -- Process each of the arguments in turn
431       (args', changed) <- Writer.listen $ mapM doarg args
432       -- See if any of the arguments changed
433       case Monoid.getAny changed of
434         True -> do
435           let (newargs', newparams', oldargs) = unzip3 args'
436           let newargs = concat newargs'
437           let newparams = concat newparams'
438           -- Create a new body that consists of a lambda for all new arguments and
439           -- the old body applied to some arguments.
440           let newbody = MkCore.mkCoreLams newparams (MkCore.mkCoreApps body oldargs)
441           -- Create a new function with the same name but a new body
442           newf <- Trans.lift $ mkFunction f newbody
443           -- Replace the original application with one of the new function to the
444           -- new arguments.
445           change $ MkCore.mkCoreApps (Var newf) newargs
446         False ->
447           -- Don't change the expression if none of the arguments changed
448           return expr
449       
450     -- If we don't have a body for the function called, leave it unchanged (it
451     -- should be a primitive function then).
452     Nothing -> return expr
453   where
454     -- Find the function called and the arguments
455     (fexpr, args) = collectArgs expr
456     Var f = fexpr
457
458     -- Process a single argument and return (args, bndrs, arg), where args are
459     -- the arguments to replace the given argument in the original
460     -- application, bndrs are the binders to include in the top-level lambda
461     -- in the new function body, and arg is the argument to apply to the old
462     -- function body.
463     doarg :: CoreExpr -> TransformMonad ([CoreExpr], [CoreBndr], CoreExpr)
464     doarg arg = do
465       repr <- isRepr arg
466       bndrs <- Trans.lift getGlobalBinders
467       let interesting var = Var.isLocalVar var && (not $ var `elem` bndrs)
468       if not repr && not (is_var arg && interesting (exprToVar arg)) && not (has_free_tyvars arg) 
469         then do
470           -- Propagate all complex arguments that are not representable, but not
471           -- arguments with free type variables (since those would require types
472           -- not known yet, which will always be known eventually).
473           -- Find interesting free variables, each of which should be passed to
474           -- the new function instead of the original function argument.
475           -- 
476           -- Interesting vars are those that are local, but not available from the
477           -- top level scope (functions from this module are defined as local, but
478           -- they're not local to this function, so we can freely move references
479           -- to them into another function).
480           let free_vars = VarSet.varSetElems $ CoreFVs.exprSomeFreeVars interesting arg
481           -- Mark the current expression as changed
482           setChanged
483           return (map Var free_vars, free_vars, arg)
484         else do
485           -- Representable types will not be propagated, and arguments with free
486           -- type variables will be propagated later.
487           -- TODO: preserve original naming?
488           id <- Trans.lift $ mkBinderFor arg "param"
489           -- Just pass the original argument to the new function, which binds it
490           -- to a new id and just pass that new id to the old function body.
491           return ([arg], [id], mkReferenceTo id) 
492 -- Leave all other expressions unchanged
493 argprop expr = return expr
494 -- Perform this transform everywhere
495 argproptop = everywhere ("argprop", argprop)
496
497 --------------------------------
498 -- Function-typed argument extraction
499 --------------------------------
500 -- This transform takes any function-typed argument that cannot be propagated
501 -- (because the function that is applied to it is a builtin function), and
502 -- puts it in a brand new top level binder. This allows us to for example
503 -- apply map to a lambda expression This will not conflict with inlinenonrep,
504 -- since that only inlines local let bindings, not top level bindings.
505 funextract, funextracttop :: Transform
506 funextract expr@(App _ _) | is_var fexpr = do
507   body_maybe <- Trans.lift $ getGlobalBind f
508   case body_maybe of
509     -- We don't have a function body for f, so we can perform this transform.
510     Nothing -> do
511       -- Find the new arguments
512       args' <- mapM doarg args
513       -- And update the arguments. We use return instead of changed, so the
514       -- changed flag doesn't get set if none of the args got changed.
515       return $ MkCore.mkCoreApps fexpr args'
516     -- We have a function body for f, leave this application to funprop
517     Just _ -> return expr
518   where
519     -- Find the function called and the arguments
520     (fexpr, args) = collectArgs expr
521     Var f = fexpr
522     -- Change any arguments that have a function type, but are not simple yet
523     -- (ie, a variable or application). This means to create a new function
524     -- for map (\f -> ...) b, but not for map (foo a) b.
525     --
526     -- We could use is_applicable here instead of is_fun, but I think
527     -- arguments to functions could only have forall typing when existential
528     -- typing is enabled. Not sure, though.
529     doarg arg | not (is_simple arg) && is_fun arg = do
530       -- Create a new top level binding that binds the argument. Its body will
531       -- be extended with lambda expressions, to take any free variables used
532       -- by the argument expression.
533       let free_vars = VarSet.varSetElems $ CoreFVs.exprFreeVars arg
534       let body = MkCore.mkCoreLams free_vars arg
535       id <- Trans.lift $ mkBinderFor body "fun"
536       Trans.lift $ addGlobalBind id body
537       -- Replace the argument with a reference to the new function, applied to
538       -- all vars it uses.
539       change $ MkCore.mkCoreApps (Var id) (map Var free_vars)
540     -- Leave all other arguments untouched
541     doarg arg = return arg
542
543 -- Leave all other expressions unchanged
544 funextract expr = return expr
545 -- Perform this transform everywhere
546 funextracttop = everywhere ("funextract", funextract)
547
548 --------------------------------
549 -- End of transformations
550 --------------------------------
551
552
553
554
555 -- What transforms to run?
556 transforms = [argproptop, funextracttop, etatop, betatop, castproptop, letremovetop, letderectop, letsimpltop, letflattop, scrutsimpltop, casesimpltop, caseremovetop, inlinenonreptop, appsimpltop, letmergetop, letremoveunusedtop, castsimpltop]
557
558 -- | Returns the normalized version of the given function.
559 getNormalized ::
560   CoreBndr -- ^ The function to get
561   -> TranslatorSession CoreExpr -- The normalized function body
562
563 getNormalized bndr = Utils.makeCached bndr tsNormalized $ do
564   if is_poly (Var bndr)
565     then
566       -- This should really only happen at the top level... TODO: Give
567       -- a different error if this happens down in the recursion.
568       error $ "\nNormalize.normalizeBind: Function " ++ show bndr ++ " is polymorphic, can't normalize"
569     else do
570       expr <- getBinding bndr
571       normalizeExpr (show bndr) expr
572
573 -- | Normalize an expression
574 normalizeExpr ::
575   String -- ^ What are we normalizing? For debug output only.
576   -> CoreSyn.CoreExpr -- ^ The expression to normalize 
577   -> TranslatorSession CoreSyn.CoreExpr -- ^ The normalized expression
578
579 normalizeExpr what expr = do
580       -- Normalize this expression
581       trace (what ++ " before normalization:\n\n" ++ showSDoc ( ppr expr ) ++ "\n") $ return ()
582       expr' <- dotransforms transforms expr
583       trace ("\n" ++ what ++ " after normalization:\n\n" ++ showSDoc ( ppr expr')) $ return ()
584       return expr'
585
586 -- | Get the value that is bound to the given binder at top level. Fails when
587 --   there is no such binding.
588 getBinding ::
589   CoreBndr -- ^ The binder to get the expression for
590   -> TranslatorSession CoreExpr -- ^ The value bound to the binder
591
592 getBinding bndr = Utils.makeCached bndr tsBindings $ do
593   -- If the binding isn't in the "cache" (bindings map), then we can't create
594   -- it out of thin air, so return an error.
595   error $ "Normalize.getBinding: Unknown function requested: " ++ show bndr
596
597 -- | Split a normalized expression into the argument binders, top level
598 --   bindings and the result binder.
599 splitNormalized ::
600   CoreExpr -- ^ The normalized expression
601   -> ([CoreBndr], [Binding], CoreBndr)
602 splitNormalized expr = (args, binds, res)
603   where
604     (args, letexpr) = CoreSyn.collectBinders expr
605     (binds, resexpr) = flattenLets letexpr
606     res = case resexpr of 
607       (Var x) -> x
608       _ -> error $ "Normalize.splitNormalized: Not in normal form: " ++ pprString expr ++ "\n"
609
610 -- | Flattens nested lets into a single list of bindings. The expression
611 --   passed does not have to be a let expression, if it isn't an empty list of
612 --   bindings is returned.
613 flattenLets ::
614   CoreExpr -- ^ The expression to flatten.
615   -> ([Binding], CoreExpr) -- ^ The bindings and resulting expression.
616 flattenLets (Let binds expr) = 
617   (bindings ++ bindings', expr')
618   where
619     -- Recursively flatten the contained expression
620     (bindings', expr') =flattenLets expr
621     -- Flatten our own bindings to remove the Rec / NonRec constructors
622     bindings = CoreSyn.flattenBinds [binds]
623 flattenLets expr = ([], expr)