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