6ee0f0f220481094179a4eab5481863f1eb70d65
[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.Accessor.Monad.Trans.State as MonadState
17 import qualified Data.Monoid as Monoid
18 import qualified Data.Map as Map
19
20 -- GHC API
21 import CoreSyn
22 import qualified CoreUtils
23 import qualified Type
24 import qualified Id
25 import qualified Var
26 import qualified Name
27 import qualified VarSet
28 import qualified CoreFVs
29 import qualified Class
30 import qualified MkCore
31 import Outputable ( showSDoc, ppr, nest )
32
33 -- Local imports
34 import CLasH.Normalize.NormalizeTypes
35 import CLasH.Translator.TranslatorTypes
36 import CLasH.Normalize.NormalizeTools
37 import CLasH.VHDL.Constants (builtinIds)
38 import qualified CLasH.Utils as Utils
39 import CLasH.Utils.Core.CoreTools
40 import CLasH.Utils.Core.BinderTools
41 import CLasH.Utils.Pretty
42
43 --------------------------------
44 -- Start of transformations
45 --------------------------------
46
47 --------------------------------
48 -- η expansion
49 --------------------------------
50 -- Make sure all parameters to the normalized functions are named by top
51 -- level lambda expressions. For this we apply η expansion to the
52 -- function body (possibly enclosed in some lambda abstractions) while
53 -- it has a function type. Eventually this will result in a function
54 -- body consisting of a bunch of nested lambdas containing a
55 -- non-function value (e.g., a complete application).
56 eta, etatop :: Transform
57 eta c expr | is_fun expr && not (is_lam expr) && all (== LambdaBody) c = do
58   let arg_ty = (fst . Type.splitFunTy . CoreUtils.exprType) expr
59   id <- Trans.lift $ mkInternalVar "param" arg_ty
60   change (Lam id (App expr (Var id)))
61 -- Leave all other expressions unchanged
62 eta c e = return e
63 etatop = everywhere ("eta", eta)
64
65 --------------------------------
66 -- β-reduction
67 --------------------------------
68 beta, betatop :: Transform
69 -- Substitute arg for x in expr. For value lambda's, also clone before
70 -- substitution.
71 beta c (App (Lam x expr) arg) | CoreSyn.isTyVar x = setChanged >> substitute x arg c expr
72                               | otherwise         = setChanged >> substitute_clone x arg c expr
73 -- Propagate the application into the let
74 beta c (App (Let binds expr) arg) = change $ Let binds (App expr arg)
75 -- Propagate the application into each of the alternatives
76 beta c (App (Case scrut b ty alts) arg) = change $ Case scrut b ty' alts'
77   where 
78     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (App expr arg))) alts
79     ty' = CoreUtils.applyTypeToArg ty arg
80 -- Leave all other expressions unchanged
81 beta c expr = return expr
82 -- Perform this transform everywhere
83 betatop = everywhere ("beta", beta)
84
85 --------------------------------
86 -- Cast propagation
87 --------------------------------
88 -- Try to move casts as much downward as possible.
89 castprop, castproptop :: Transform
90 castprop c (Cast (Let binds expr) ty) = change $ Let binds (Cast expr ty)
91 castprop c expr@(Cast (Case scrut b _ alts) ty) = change (Case scrut b ty alts')
92   where
93     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (Cast expr ty))) alts
94 -- Leave all other expressions unchanged
95 castprop c expr = return expr
96 -- Perform this transform everywhere
97 castproptop = everywhere ("castprop", castprop)
98
99 --------------------------------
100 -- Cast simplification. Mostly useful for state packing and unpacking, but
101 -- perhaps for others as well.
102 --------------------------------
103 castsimpl, castsimpltop :: Transform
104 castsimpl c expr@(Cast val ty) = do
105   -- Don't extract values that are already simpl
106   local_var <- Trans.lift $ is_local_var val
107   -- Don't extract values that are not representable, to prevent loops with
108   -- inlinenonrep
109   repr <- isRepr val
110   if (not local_var) && repr
111     then do
112       -- Generate a binder for the expression
113       id <- Trans.lift $ mkBinderFor val "castval"
114       -- Extract the expression
115       change $ Let (NonRec id val) (Cast (Var id) ty)
116     else
117       return expr
118 -- Leave all other expressions unchanged
119 castsimpl c expr = return expr
120 -- Perform this transform everywhere
121 castsimpltop = everywhere ("castsimpl", castsimpl)
122
123
124 --------------------------------
125 -- Lambda simplication
126 --------------------------------
127 -- Ensure that a lambda always evaluates to a let expressions or a simple
128 -- variable reference.
129 lambdasimpl, lambdasimpltop :: Transform
130 -- Don't simplify a lambda that evaluates to let, since this is already
131 -- normal form (and would cause infinite loops).
132 lambdasimpl c expr@(Lam _ (Let _ _)) = return expr
133 -- Put the of a lambda in its own binding, but not when the expression is
134 -- already a local variable, or not representable (to prevent loops with
135 -- inlinenonrep).
136 lambdasimpl c expr@(Lam bndr res) = do
137   repr <- isRepr res
138   local_var <- Trans.lift $ is_local_var res
139   if not local_var && repr
140     then do
141       id <- Trans.lift $ mkBinderFor res "res"
142       change $ Lam bndr (Let (NonRec id res) (Var id))
143     else
144       -- If the result is already a local var or not representable, don't
145       -- extract it.
146       return expr
147
148 -- Leave all other expressions unchanged
149 lambdasimpl c expr = return expr
150 -- Perform this transform everywhere
151 lambdasimpltop = everywhere ("lambdasimpl", lambdasimpl)
152
153 --------------------------------
154 -- let derecursification
155 --------------------------------
156 letderec, letderectop :: Transform
157 letderec c expr@(Let (Rec binds) res) = case liftable of
158   -- Nothing is liftable, just return
159   [] -> return expr
160   -- Something can be lifted, generate a new let expression
161   _ -> change $ mkNonRecLets liftable (Let (Rec nonliftable) res)
162   where
163     -- Make a list of all the binders bound in this recursive let
164     bndrs = map fst binds
165     -- See which bindings are liftable
166     (liftable, nonliftable) = List.partition canlift binds
167     -- Any expression that does not use any of the binders in this recursive let
168     -- can be lifted into a nonrec let. It can't use its own binder either,
169     -- since that would mean the binding is self-recursive and should be in a
170     -- single bind recursive let.
171     canlift (bndr, e) = not $ expr_uses_binders bndrs e
172 -- Leave all other expressions unchanged
173 letderec c expr = return expr
174 -- Perform this transform everywhere
175 letderectop = everywhere ("letderec", letderec)
176
177 --------------------------------
178 -- let simplification
179 --------------------------------
180 letsimpl, letsimpltop :: Transform
181 -- Don't simplify a let that evaluates to another let, since this is already
182 -- normal form (and would cause infinite loops with letflat below).
183 letsimpl c expr@(Let _ (Let _ _)) = return expr
184 -- Put the "in ..." value of a let in its own binding, but not when the
185 -- expression is already a local variable, or not representable (to prevent loops with inlinenonrep).
186 letsimpl c expr@(Let binds res) = do
187   repr <- isRepr res
188   local_var <- Trans.lift $ is_local_var res
189   if not local_var && repr
190     then do
191       -- If the result is not a local var already (to prevent loops with
192       -- ourselves), extract it.
193       id <- Trans.lift $ mkBinderFor res "foo"
194       change $ Let binds (Let (NonRec id  res) (Var id))
195     else
196       -- If the result is already a local var, don't extract it.
197       return expr
198
199 -- Leave all other expressions unchanged
200 letsimpl c expr = return expr
201 -- Perform this transform everywhere
202 letsimpltop = everywhere ("letsimpl", letsimpl)
203
204 --------------------------------
205 -- let flattening
206 --------------------------------
207 -- Takes a let that binds another let, and turns that into two nested lets.
208 -- e.g., from:
209 -- let b = (let b' = expr' in res') in res
210 -- to:
211 -- let b' = expr' in (let b = res' in res)
212 letflat, letflattop :: Transform
213 -- Turn a nonrec let that binds a let into two nested lets.
214 letflat c (Let (NonRec b (Let binds  res')) res) = 
215   change $ Let binds (Let (NonRec b res') res)
216 letflat c (Let (Rec binds) expr) = do
217   -- Flatten each binding.
218   binds' <- Utils.concatM $ Monad.mapM flatbind binds
219   -- Return the new let. We don't use change here, since possibly nothing has
220   -- changed. If anything has changed, flatbind has already flagged that
221   -- change.
222   return $ Let (Rec binds') expr
223   where
224     -- Turns a binding of a let into a multiple bindings, or any other binding
225     -- into a list with just that binding
226     flatbind :: (CoreBndr, CoreExpr) -> TransformMonad [(CoreBndr, CoreExpr)]
227     flatbind (b, Let (Rec binds) expr) = change ((b, expr):binds)
228     flatbind (b, Let (NonRec b' expr') expr) = change [(b, expr), (b', expr')]
229     flatbind (b, expr) = return [(b, expr)]
230 -- Leave all other expressions unchanged
231 letflat c expr = return expr
232 -- Perform this transform everywhere
233 letflattop = everywhere ("letflat", letflat)
234
235 --------------------------------
236 -- empty let removal
237 --------------------------------
238 -- Remove empty (recursive) lets
239 letremove, letremovetop :: Transform
240 letremove c (Let (Rec []) res) = change res
241 -- Leave all other expressions unchanged
242 letremove c expr = return expr
243 -- Perform this transform everywhere
244 letremovetop = everywhere ("letremove", letremove)
245
246 --------------------------------
247 -- Simple let binding removal
248 --------------------------------
249 -- Remove a = b bindings from let expressions everywhere
250 letremovesimpletop :: Transform
251 letremovesimpletop = everywhere ("letremovesimple", inlinebind (\(b, e) -> Trans.lift $ is_local_var e))
252
253 --------------------------------
254 -- Unused let binding removal
255 --------------------------------
256 letremoveunused, letremoveunusedtop :: Transform
257 letremoveunused c expr@(Let (NonRec b bound) res) = do
258   let used = expr_uses_binders [b] res
259   if used
260     then return expr
261     else change res
262 letremoveunused c expr@(Let (Rec binds) res) = do
263   -- Filter out all unused binds.
264   let binds' = filter dobind binds
265   -- Only set the changed flag if binds got removed
266   changeif (length binds' /= length binds) (Let (Rec binds') res)
267     where
268       bound_exprs = map snd binds
269       -- For each bind check if the bind is used by res or any of the bound
270       -- expressions
271       dobind (bndr, _) = any (expr_uses_binders [bndr]) (res:bound_exprs)
272 -- Leave all other expressions unchanged
273 letremoveunused c expr = return expr
274 letremoveunusedtop = everywhere ("letremoveunused", letremoveunused)
275
276 {-
277 --------------------------------
278 -- Identical let binding merging
279 --------------------------------
280 -- Merge two bindings in a let if they are identical 
281 -- TODO: We would very much like to use GHC's CSE module for this, but that
282 -- doesn't track if something changed or not, so we can't use it properly.
283 letmerge, letmergetop :: Transform
284 letmerge c expr@(Let _ _) = do
285   let (binds, res) = flattenLets expr
286   binds' <- domerge binds
287   return $ mkNonRecLets binds' res
288   where
289     domerge :: [(CoreBndr, CoreExpr)] -> TransformMonad [(CoreBndr, CoreExpr)]
290     domerge [] = return []
291     domerge (e:es) = do 
292       es' <- mapM (mergebinds e) es
293       es'' <- domerge es'
294       return (e:es'')
295
296     -- Uses the second bind to simplify the second bind, if applicable.
297     mergebinds :: (CoreBndr, CoreExpr) -> (CoreBndr, CoreExpr) -> TransformMonad (CoreBndr, CoreExpr)
298     mergebinds (b1, e1) (b2, e2)
299       -- Identical expressions? Replace the second binding with a reference to
300       -- the first binder.
301       | CoreUtils.cheapEqExpr e1 e2 = change $ (b2, Var b1)
302       -- Different expressions? Don't change
303       | otherwise = return (b2, e2)
304 -- Leave all other expressions unchanged
305 letmerge c expr = return expr
306 letmergetop = everywhere ("letmerge", letmerge)
307 -}
308
309 --------------------------------
310 -- Non-representable binding inlining
311 --------------------------------
312 -- Remove a = B bindings, with B of a non-representable type, from let
313 -- expressions everywhere. This means that any value that we can't generate a
314 -- signal for, will be inlined and hopefully turned into something we can
315 -- represent.
316 --
317 -- This is a tricky function, which is prone to create loops in the
318 -- transformations. To fix this, we make sure that no transformation will
319 -- create a new let binding with a non-representable type. These other
320 -- transformations will just not work on those function-typed values at first,
321 -- but the other transformations (in particular β-reduction) should make sure
322 -- that the type of those values eventually becomes representable.
323 inlinenonreptop :: Transform
324 inlinenonreptop = everywhere ("inlinenonrep", inlinebind ((Monad.liftM not) . isRepr . snd))
325
326 --------------------------------
327 -- Top level function inlining
328 --------------------------------
329 -- This transformation inlines simple top level bindings. Simple
330 -- currently means that the body is only a single application (though
331 -- the complexity of the arguments is not currently checked) or that the
332 -- normalized form only contains a single binding. This should catch most of the
333 -- cases where a top level function is created that simply calls a type class
334 -- method with a type and dictionary argument, e.g.
335 --   fromInteger = GHC.Num.fromInteger (SizedWord D8) $dNum
336 -- which is later called using simply
337 --   fromInteger (smallInteger 10)
338 --
339 -- These useless wrappers are created by GHC automatically. If we don't
340 -- inline them, we get loads of useless components cluttering the
341 -- generated VHDL.
342 --
343 -- Note that the inlining could also inline simple functions defined by
344 -- the user, not just GHC generated functions. It turns out to be near
345 -- impossible to reliably determine what functions are generated and
346 -- what functions are user-defined. Instead of guessing (which will
347 -- inline less than we want) we will just inline all simple functions.
348 --
349 -- Only functions that are actually completely applied and bound by a
350 -- variable in a let expression are inlined. These are the expressions
351 -- that will eventually generate instantiations of trivial components.
352 -- By not inlining any other reference, we also prevent looping problems
353 -- with funextract and inlinedict.
354 inlinetoplevel, inlinetopleveltop :: Transform
355 inlinetoplevel (LetBinding:_) expr | not (is_fun expr) =
356   case collectArgs expr of
357         (Var f, args) -> do
358           body_maybe <- needsInline f
359           case body_maybe of
360                 Just body -> do
361                         -- Regenerate all uniques in the to-be-inlined expression
362                         body_uniqued <- Trans.lift $ genUniques body
363                         -- And replace the variable reference with the unique'd body.
364                         change (mkApps body_uniqued args)
365                         -- No need to inline
366                 Nothing -> return expr
367         -- This is not an application of a binder, leave it unchanged.
368         _ -> return expr
369
370 -- Leave all other expressions unchanged
371 inlinetoplevel c expr = return expr
372 inlinetopleveltop = everywhere ("inlinetoplevel", inlinetoplevel)
373   
374 -- | Does the given binder need to be inlined? If so, return the body to
375 -- be used for inlining.
376 needsInline :: CoreBndr -> TransformMonad (Maybe CoreExpr)
377 needsInline f = do
378   body_maybe <- Trans.lift $ getGlobalBind f
379   case body_maybe of
380     -- No body available?
381     Nothing -> return Nothing
382     Just body -> case CoreSyn.collectArgs body of
383       -- The body is some (top level) binder applied to 0 or more
384       -- arguments. That should be simple enough to inline.
385       (Var f, args) -> return $ Just body
386       -- Body is more complicated, try normalizing it
387       _ -> do
388         norm_maybe <- Trans.lift $ getNormalized_maybe f
389         case norm_maybe of
390           -- Noth normalizeable
391           Nothing -> return Nothing 
392           Just norm -> case splitNormalized norm of
393             -- The function has just a single binding, so that's simple
394             -- enough to inline.
395             (args, [bind], res) -> return $ Just norm
396             -- More complicated function, don't inline
397             _ -> return Nothing
398             
399 --------------------------------
400 -- Dictionary inlining
401 --------------------------------
402 -- Inline all top level dictionaries, that are in a position where
403 -- classopresolution can actually resolve them. This makes this
404 -- transformation look similar to classoperesolution below, but we'll
405 -- keep them separated for clarity. By not inlining other dictionaries,
406 -- we prevent expression sizes exploding when huge type level integer
407 -- dictionaries are inlined which can never be expanded (in casts, for
408 -- example).
409 inlinedict c expr@(App (App (Var sel) ty) (Var dict)) | not is_builtin && is_classop = do
410   body_maybe <- Trans.lift $ getGlobalBind dict
411   case body_maybe of
412     -- No body available (no source available, or a local variable /
413     -- argument)
414     Nothing -> return expr
415     Just body -> change (App (App (Var sel) ty) body)
416   where
417     -- Is this a builtin function / method?
418     is_builtin = elem (Name.getOccString sel) builtinIds
419     -- Are we dealing with a class operation selector?
420     is_classop = Maybe.isJust (Id.isClassOpId_maybe sel)
421
422 -- Leave all other expressions unchanged
423 inlinedict c expr = return expr
424 inlinedicttop = everywhere ("inlinedict", inlinedict)
425
426 --------------------------------
427 -- ClassOp resolution
428 --------------------------------
429 -- Resolves any class operation to the actual operation whenever
430 -- possible. Class methods (as well as parent dictionary selectors) are
431 -- special "functions" that take a type and a dictionary and evaluate to
432 -- the corresponding method. A dictionary is nothing more than a
433 -- special dataconstructor applied to the type the dictionary is for,
434 -- each of the superclasses and all of the class method definitions for
435 -- that particular type. Since dictionaries all always inlined (top
436 -- levels dictionaries are inlined by inlinedict, local dictionaries are
437 -- inlined by inlinenonrep), we will eventually have something like:
438 --
439 --   baz
440 --     @ CLasH.HardwareTypes.Bit
441 --     (D:Baz @ CLasH.HardwareTypes.Bit bitbaz)
442 --
443 -- Here, baz is the method selector for the baz method, while
444 -- D:Baz is the dictionary constructor for the Baz and bitbaz is the baz
445 -- method defined in the Baz Bit instance declaration.
446 --
447 -- To resolve this, we can look at the ClassOp IdInfo from the baz Id,
448 -- which contains the Class it is defined for. From the Class, we can
449 -- get a list of all selectors (both parent class selectors as well as
450 -- method selectors). Since the arguments to D:Baz (after the type
451 -- argument) correspond exactly to this list, we then look up baz in
452 -- that list and replace the entire expression by the corresponding 
453 -- argument to D:Baz.
454 --
455 -- We don't resolve methods that have a builtin translation (such as
456 -- ==), since the actual implementation is not always (easily)
457 -- translateable. For example, when deriving ==, GHC generates code
458 -- using $con2tag functions to translate a datacon to an int and compare
459 -- that with GHC.Prim.==# . Better to avoid that for now.
460 classopresolution, classopresolutiontop :: Transform
461 classopresolution c expr@(App (App (Var sel) ty) dict) | not is_builtin =
462   case Id.isClassOpId_maybe sel of
463     -- Not a class op selector
464     Nothing -> return expr
465     Just cls -> case collectArgs dict of
466       (_, []) -> return expr -- Dict is not an application (e.g., not inlined yet)
467       (Var dictdc, (ty':selectors)) | not (Maybe.isJust (Id.isDataConId_maybe dictdc)) -> return expr -- Dictionary is not a datacon yet (but e.g., a top level binder)
468                                 | tyargs_neq ty ty' -> error $ "Normalize.classopresolution: Applying class selector to dictionary without matching type?\n" ++ pprString expr
469                                 | otherwise ->
470         let selector_ids = Class.classSelIds cls in
471         -- Find the selector used in the class' list of selectors
472         case List.elemIndex sel selector_ids of
473           Nothing -> error $ "Normalize.classopresolution: Selector not found in class' selector list? This should not happen!\nExpression: " ++ pprString expr ++ "\nClass: " ++ show cls ++ "\nSelectors: " ++ show selector_ids
474           -- Get the corresponding argument from the dictionary
475           Just n -> change (selectors!!n)
476       (_, _) -> return expr -- Not applying a variable? Don't touch
477   where
478     -- Compare two type arguments, returning True if they are _not_
479     -- equal
480     tyargs_neq (Type ty1) (Type ty2) = not $ Type.coreEqType ty1 ty2
481     tyargs_neq _ _ = True
482     -- Is this a builtin function / method?
483     is_builtin = elem (Name.getOccString sel) builtinIds
484
485 -- Leave all other expressions unchanged
486 classopresolution c expr = return expr
487 -- Perform this transform everywhere
488 classopresolutiontop = everywhere ("classopresolution", classopresolution)
489
490 --------------------------------
491 -- Scrutinee simplification
492 --------------------------------
493 scrutsimpl,scrutsimpltop :: Transform
494 -- Don't touch scrutinees that are already simple
495 scrutsimpl c expr@(Case (Var _) _ _ _) = return expr
496 -- Replace all other cases with a let that binds the scrutinee and a new
497 -- simple scrutinee, but only when the scrutinee is representable (to prevent
498 -- loops with inlinenonrep, though I don't think a non-representable scrutinee
499 -- will be supported anyway...) 
500 scrutsimpl c expr@(Case scrut b ty alts) = do
501   repr <- isRepr scrut
502   if repr
503     then do
504       id <- Trans.lift $ mkBinderFor scrut "scrut"
505       change $ Let (NonRec id scrut) (Case (Var id) b ty alts)
506     else
507       return expr
508 -- Leave all other expressions unchanged
509 scrutsimpl c expr = return expr
510 -- Perform this transform everywhere
511 scrutsimpltop = everywhere ("scrutsimpl", scrutsimpl)
512
513 --------------------------------
514 -- Scrutinee binder removal
515 --------------------------------
516 -- A case expression can have an extra binder, to which the scrutinee is bound
517 -- after bringing it to WHNF. This is used for forcing evaluation of strict
518 -- arguments. Since strictness does not matter for us (rather, everything is
519 -- sort of strict), this binder is ignored when generating VHDL, and must thus
520 -- be wild in the normal form.
521 scrutbndrremove, scrutbndrremovetop :: Transform
522 -- If the scrutinee is already simple, and the bndr is not wild yet, replace
523 -- all occurences of the binder with the scrutinee variable.
524 scrutbndrremove c (Case (Var scrut) bndr ty alts) | bndr_used = do
525     alts' <- mapM subs_bndr alts
526     change $ Case (Var scrut) wild ty alts'
527   where
528     is_used (_, _, expr) = expr_uses_binders [bndr] expr
529     bndr_used = or $ map is_used alts
530     subs_bndr (con, bndrs, expr) = do
531       expr' <- substitute bndr (Var scrut) c expr
532       return (con, bndrs, expr')
533     wild = MkCore.mkWildBinder (Id.idType bndr)
534 -- Leave all other expressions unchanged
535 scrutbndrremove c expr = return expr
536 scrutbndrremovetop = everywhere ("scrutbndrremove", scrutbndrremove)
537
538 --------------------------------
539 -- Case binder wildening
540 --------------------------------
541 casesimpl, casesimpltop :: Transform
542 -- This is already a selector case (or, if x does not appear in bndrs, a very
543 -- simple case statement that will be removed by caseremove below). Just leave
544 -- it be.
545 casesimpl c expr@(Case scrut b ty [(con, bndrs, Var x)]) = return expr
546 -- Make sure that all case alternatives have only wild binders and simple
547 -- expressions.
548 -- This is done by creating a new let binding for each non-wild binder, which
549 -- is bound to a new simple selector case statement and for each complex
550 -- expression. We do this only for representable types, to prevent loops with
551 -- inlinenonrep.
552 casesimpl c expr@(Case scrut bndr ty alts) | not bndr_used = do
553   (bindingss, alts') <- (Monad.liftM unzip) $ mapM doalt alts
554   let bindings = concat bindingss
555   -- Replace the case with a let with bindings and a case
556   let newlet = mkNonRecLets bindings (Case scrut bndr ty alts')
557   -- If there are no non-wild binders, or this case is already a simple
558   -- selector (i.e., a single alt with exactly one binding), already a simple
559   -- selector altan no bindings (i.e., no wild binders in the original case),
560   -- don't change anything, otherwise, replace the case.
561   if null bindings then return expr else change newlet 
562   where
563   -- Check if the scrutinee binder is used
564   is_used (_, _, expr) = expr_uses_binders [bndr] expr
565   bndr_used = or $ map is_used alts
566   -- Generate a single wild binder, since they are all the same
567   wild = MkCore.mkWildBinder
568   -- Wilden the binders of one alt, producing a list of bindings as a
569   -- sideeffect.
570   doalt :: CoreAlt -> TransformMonad ([(CoreBndr, CoreExpr)], CoreAlt)
571   doalt (con, bndrs, expr) = do
572     -- Make each binder wild, if possible
573     bndrs_res <- Monad.zipWithM dobndr bndrs [0..]
574     let (newbndrs, bindings_maybe) = unzip bndrs_res
575     -- Extract a complex expression, if possible. For this we check if any of
576     -- the new list of bndrs are used by expr. We can't use free_vars here,
577     -- since that looks at the old bndrs.
578     let uses_bndrs = not $ VarSet.isEmptyVarSet $ CoreFVs.exprSomeFreeVars (`elem` newbndrs) expr
579     (exprbinding_maybe, expr') <- doexpr expr uses_bndrs
580     -- Create a new alternative
581     let newalt = (con, newbndrs, expr')
582     let bindings = Maybe.catMaybes (bindings_maybe ++ [exprbinding_maybe])
583     return (bindings, newalt)
584     where
585       -- Make wild alternatives for each binder
586       wildbndrs = map (\bndr -> MkCore.mkWildBinder (Id.idType bndr)) bndrs
587       -- A set of all the binders that are used by the expression
588       free_vars = CoreFVs.exprSomeFreeVars (`elem` bndrs) expr
589       -- Look at the ith binder in the case alternative. Return a new binder
590       -- for it (either the same one, or a wild one) and optionally a let
591       -- binding containing a case expression.
592       dobndr :: CoreBndr -> Int -> TransformMonad (CoreBndr, Maybe (CoreBndr, CoreExpr))
593       dobndr b i = do
594         repr <- isRepr b
595         -- Is b wild (e.g., not a free var of expr. Since b is only in scope
596         -- in expr, this means that b is unused if expr does not use it.)
597         let wild = not (VarSet.elemVarSet b free_vars)
598         -- Create a new binding for any representable binder that is not
599         -- already wild and is representable (to prevent loops with
600         -- inlinenonrep).
601         if (not wild) && repr
602           then do
603             -- Create on new binder that will actually capture a value in this
604             -- case statement, and return it.
605             let bty = (Id.idType b)
606             id <- Trans.lift $ mkInternalVar "sel" bty
607             let binders = take i wildbndrs ++ [id] ++ drop (i+1) wildbndrs
608             let caseexpr = Case scrut b bty [(con, binders, Var id)]
609             return (wildbndrs!!i, Just (b, caseexpr))
610           else 
611             -- Just leave the original binder in place, and don't generate an
612             -- extra selector case.
613             return (b, Nothing)
614       -- Process the expression of a case alternative. Accepts an expression
615       -- and whether this expression uses any of the binders in the
616       -- alternative. Returns an optional new binding and a new expression.
617       doexpr :: CoreExpr -> Bool -> TransformMonad (Maybe (CoreBndr, CoreExpr), CoreExpr)
618       doexpr expr uses_bndrs = do
619         local_var <- Trans.lift $ is_local_var expr
620         repr <- isRepr expr
621         -- Extract any expressions that do not use any binders from this
622         -- alternative, is not a local var already and is representable (to
623         -- prevent loops with inlinenonrep).
624         if (not uses_bndrs) && (not local_var) && repr
625           then do
626             id <- Trans.lift $ mkBinderFor expr "caseval"
627             -- We don't flag a change here, since casevalsimpl will do that above
628             -- based on Just we return here.
629             return (Just (id, expr), Var id)
630           else
631             -- Don't simplify anything else
632             return (Nothing, expr)
633 -- Leave all other expressions unchanged
634 casesimpl c expr = return expr
635 -- Perform this transform everywhere
636 casesimpltop = everywhere ("casesimpl", casesimpl)
637
638 --------------------------------
639 -- Case removal
640 --------------------------------
641 -- Remove case statements that have only a single alternative and only wild
642 -- binders.
643 caseremove, caseremovetop :: Transform
644 -- Replace a useless case by the value of its single alternative
645 caseremove c (Case scrut b ty [(con, bndrs, expr)]) | not usesvars = change expr
646     -- Find if any of the binders are used by expr
647     where usesvars = (not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` b:bndrs))) expr
648 -- Leave all other expressions unchanged
649 caseremove c expr = return expr
650 -- Perform this transform everywhere
651 caseremovetop = everywhere ("caseremove", caseremove)
652
653 --------------------------------
654 -- Argument extraction
655 --------------------------------
656 -- Make sure that all arguments of a representable type are simple variables.
657 appsimpl, appsimpltop :: Transform
658 -- Simplify all representable arguments. Do this by introducing a new Let
659 -- that binds the argument and passing the new binder in the application.
660 appsimpl c expr@(App f arg) = do
661   -- Check runtime representability
662   repr <- isRepr arg
663   local_var <- Trans.lift $ is_local_var arg
664   if repr && not local_var
665     then do -- Extract representable arguments
666       id <- Trans.lift $ mkBinderFor arg "arg"
667       change $ Let (NonRec id arg) (App f (Var id))
668     else -- Leave non-representable arguments unchanged
669       return expr
670 -- Leave all other expressions unchanged
671 appsimpl c expr = return expr
672 -- Perform this transform everywhere
673 appsimpltop = everywhere ("appsimpl", appsimpl)
674
675 --------------------------------
676 -- Function-typed argument propagation
677 --------------------------------
678 -- Remove all applications to function-typed arguments, by duplication the
679 -- function called with the function-typed parameter replaced by the free
680 -- variables of the argument passed in.
681 argprop, argproptop :: Transform
682 -- Transform any application of a named function (i.e., skip applications of
683 -- lambda's). Also skip applications that have arguments with free type
684 -- variables, since we can't inline those.
685 argprop c expr@(App _ _) | is_var fexpr = do
686   -- Find the body of the function called
687   body_maybe <- Trans.lift $ getGlobalBind f
688   case body_maybe of
689     Just body -> do
690       -- Process each of the arguments in turn
691       (args', changed) <- Writer.listen $ mapM doarg args
692       -- See if any of the arguments changed
693       case Monoid.getAny changed of
694         True -> do
695           let (newargs', newparams', oldargs) = unzip3 args'
696           let newargs = concat newargs'
697           let newparams = concat newparams'
698           -- Create a new body that consists of a lambda for all new arguments and
699           -- the old body applied to some arguments.
700           let newbody = MkCore.mkCoreLams newparams (MkCore.mkCoreApps body oldargs)
701           -- Create a new function with the same name but a new body
702           newf <- Trans.lift $ mkFunction f newbody
703
704           Trans.lift $ MonadState.modify tsInitStates (\ismap ->
705             let init_state_maybe = Map.lookup f ismap in
706             case init_state_maybe of
707               Nothing -> ismap
708               Just init_state -> Map.insert newf init_state ismap)
709           -- Replace the original application with one of the new function to the
710           -- new arguments.
711           change $ MkCore.mkCoreApps (Var newf) newargs
712         False ->
713           -- Don't change the expression if none of the arguments changed
714           return expr
715       
716     -- If we don't have a body for the function called, leave it unchanged (it
717     -- should be a primitive function then).
718     Nothing -> return expr
719   where
720     -- Find the function called and the arguments
721     (fexpr, args) = collectArgs expr
722     Var f = fexpr
723
724     -- Process a single argument and return (args, bndrs, arg), where args are
725     -- the arguments to replace the given argument in the original
726     -- application, bndrs are the binders to include in the top-level lambda
727     -- in the new function body, and arg is the argument to apply to the old
728     -- function body.
729     doarg :: CoreExpr -> TransformMonad ([CoreExpr], [CoreBndr], CoreExpr)
730     doarg arg = do
731       repr <- isRepr arg
732       bndrs <- Trans.lift getGlobalBinders
733       let interesting var = Var.isLocalVar var && (var `notElem` bndrs)
734       if not repr && not (is_var arg && interesting (exprToVar arg)) && not (has_free_tyvars arg) 
735         then do
736           -- Propagate all complex arguments that are not representable, but not
737           -- arguments with free type variables (since those would require types
738           -- not known yet, which will always be known eventually).
739           -- Find interesting free variables, each of which should be passed to
740           -- the new function instead of the original function argument.
741           -- 
742           -- Interesting vars are those that are local, but not available from the
743           -- top level scope (functions from this module are defined as local, but
744           -- they're not local to this function, so we can freely move references
745           -- to them into another function).
746           let free_vars = VarSet.varSetElems $ CoreFVs.exprSomeFreeVars interesting arg
747           -- Mark the current expression as changed
748           setChanged
749           -- TODO: Clone the free_vars (and update references in arg), since
750           -- this might cause conflicts if two arguments that are propagated
751           -- share a free variable. Also, we are now introducing new variables
752           -- into a function that are not fresh, which violates the binder
753           -- uniqueness invariant.
754           return (map Var free_vars, free_vars, arg)
755         else do
756           -- Representable types will not be propagated, and arguments with free
757           -- type variables will be propagated later.
758           -- Note that we implicitly remove any type variables in the type of
759           -- the original argument by using the type of the actual argument
760           -- for the new formal parameter.
761           -- TODO: preserve original naming?
762           id <- Trans.lift $ mkBinderFor arg "param"
763           -- Just pass the original argument to the new function, which binds it
764           -- to a new id and just pass that new id to the old function body.
765           return ([arg], [id], mkReferenceTo id) 
766 -- Leave all other expressions unchanged
767 argprop c expr = return expr
768 -- Perform this transform everywhere
769 argproptop = everywhere ("argprop", argprop)
770
771 --------------------------------
772 -- Function-typed argument extraction
773 --------------------------------
774 -- This transform takes any function-typed argument that cannot be propagated
775 -- (because the function that is applied to it is a builtin function), and
776 -- puts it in a brand new top level binder. This allows us to for example
777 -- apply map to a lambda expression This will not conflict with inlinenonrep,
778 -- since that only inlines local let bindings, not top level bindings.
779 funextract, funextracttop :: Transform
780 funextract c expr@(App _ _) | is_var fexpr = do
781   body_maybe <- Trans.lift $ getGlobalBind f
782   case body_maybe of
783     -- We don't have a function body for f, so we can perform this transform.
784     Nothing -> do
785       -- Find the new arguments
786       args' <- mapM doarg args
787       -- And update the arguments. We use return instead of changed, so the
788       -- changed flag doesn't get set if none of the args got changed.
789       return $ MkCore.mkCoreApps fexpr args'
790     -- We have a function body for f, leave this application to funprop
791     Just _ -> return expr
792   where
793     -- Find the function called and the arguments
794     (fexpr, args) = collectArgs expr
795     Var f = fexpr
796     -- Change any arguments that have a function type, but are not simple yet
797     -- (ie, a variable or application). This means to create a new function
798     -- for map (\f -> ...) b, but not for map (foo a) b.
799     --
800     -- We could use is_applicable here instead of is_fun, but I think
801     -- arguments to functions could only have forall typing when existential
802     -- typing is enabled. Not sure, though.
803     doarg arg | not (is_simple arg) && is_fun arg = do
804       -- Create a new top level binding that binds the argument. Its body will
805       -- be extended with lambda expressions, to take any free variables used
806       -- by the argument expression.
807       let free_vars = VarSet.varSetElems $ CoreFVs.exprFreeVars arg
808       let body = MkCore.mkCoreLams free_vars arg
809       id <- Trans.lift $ mkBinderFor body "fun"
810       Trans.lift $ addGlobalBind id body
811       -- Replace the argument with a reference to the new function, applied to
812       -- all vars it uses.
813       change $ MkCore.mkCoreApps (Var id) (map Var free_vars)
814     -- Leave all other arguments untouched
815     doarg arg = return arg
816
817 -- Leave all other expressions unchanged
818 funextract c expr = return expr
819 -- Perform this transform everywhere
820 funextracttop = everywhere ("funextract", funextract)
821
822 --------------------------------
823 -- Ensure that a function that just returns another function (or rather,
824 -- another top-level binder) is still properly normalized. This is a temporary
825 -- solution, we should probably integrate this pass with lambdasimpl and
826 -- letsimpl instead.
827 --------------------------------
828 simplrestop c expr@(Lam _ _) = return expr
829 simplrestop c expr@(Let _ _) = return expr
830 simplrestop c expr = do
831   local_var <- Trans.lift $ is_local_var expr
832   -- Don't extract values that are not representable, to prevent loops with
833   -- inlinenonrep
834   repr <- isRepr expr
835   if local_var || not repr
836     then
837       return expr
838     else do
839       id <- Trans.lift $ mkBinderFor expr "res" 
840       change $ Let (NonRec id expr) (Var id)
841 --------------------------------
842 -- End of transformations
843 --------------------------------
844
845
846
847
848 -- What transforms to run?
849 transforms = [inlinedicttop, inlinetopleveltop, classopresolutiontop, argproptop, funextracttop, etatop, betatop, castproptop, letremovesimpletop, letderectop, letremovetop, letsimpltop, letflattop, scrutsimpltop, scrutbndrremovetop, casesimpltop, caseremovetop, inlinenonreptop, appsimpltop, letremoveunusedtop, castsimpltop, lambdasimpltop, simplrestop]
850
851 -- | Returns the normalized version of the given function, or an error
852 -- if it is not a known global binder.
853 getNormalized ::
854   CoreBndr -- ^ The function to get
855   -> TranslatorSession CoreExpr -- The normalized function body
856 getNormalized bndr = do
857   norm <- getNormalized_maybe bndr
858   return $ Maybe.fromMaybe
859     (error $ "Normalize.getNormalized: Unknown or non-representable function requested: " ++ show bndr)
860     norm
861
862 -- | Returns the normalized version of the given function, or Nothing
863 -- when the binder is not a known global binder or is not normalizeable.
864 getNormalized_maybe ::
865   CoreBndr -- ^ The function to get
866   -> TranslatorSession (Maybe CoreExpr) -- The normalized function body
867
868 getNormalized_maybe bndr = do
869     expr_maybe <- getGlobalBind bndr
870     normalizeable <- isNormalizeable' bndr
871     if not normalizeable || Maybe.isNothing expr_maybe
872       then
873         -- Binder not normalizeable or not found
874         return Nothing
875       else if is_poly (Var bndr)
876         then
877           -- This should really only happen at the top level... TODO: Give
878           -- a different error if this happens down in the recursion.
879           error $ "\nNormalize.normalizeBind: Function " ++ show bndr ++ " is polymorphic, can't normalize"
880         else do
881           -- Binder found and is monomorphic. Normalize the expression
882           -- and cache the result.
883           normalized <- Utils.makeCached bndr tsNormalized $ 
884             normalizeExpr (show bndr) (Maybe.fromJust expr_maybe)
885           return (Just normalized)
886
887 -- | Normalize an expression
888 normalizeExpr ::
889   String -- ^ What are we normalizing? For debug output only.
890   -> CoreSyn.CoreExpr -- ^ The expression to normalize 
891   -> TranslatorSession CoreSyn.CoreExpr -- ^ The normalized expression
892
893 normalizeExpr what expr = do
894       expr_uniqued <- genUniques expr
895       -- Normalize this expression
896       trace (what ++ " before normalization:\n\n" ++ showSDoc ( ppr expr_uniqued ) ++ "\n") $ return ()
897       expr' <- dotransforms transforms expr_uniqued
898       trace ("\n" ++ what ++ " after normalization:\n\n" ++ showSDoc ( ppr expr')) $ return ()
899       return expr'
900
901 -- | Split a normalized expression into the argument binders, top level
902 --   bindings and the result binder.
903 splitNormalized ::
904   CoreExpr -- ^ The normalized expression
905   -> ([CoreBndr], [Binding], CoreBndr)
906 splitNormalized expr = (args, binds, res)
907   where
908     (args, letexpr) = CoreSyn.collectBinders expr
909     (binds, resexpr) = flattenLets letexpr
910     res = case resexpr of 
911       (Var x) -> x
912       _ -> error $ "Normalize.splitNormalized: Not in normal form: " ++ pprString expr ++ "\n"