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