Add a new "section" for type-class transformations.
[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 -- Don't touch scrutinees that are already simple
410 scrutsimpl c expr@(Case (Var _) _ _ _) = return expr
411 -- Replace all other cases with a let that binds the scrutinee and a new
412 -- simple scrutinee, but only when the scrutinee is representable (to prevent
413 -- loops with inlinenonrep, though I don't think a non-representable scrutinee
414 -- will be supported anyway...) 
415 scrutsimpl c expr@(Case scrut b ty alts) = do
416   repr <- isRepr scrut
417   if repr
418     then do
419       id <- Trans.lift $ mkBinderFor scrut "scrut"
420       change $ Let (NonRec id scrut) (Case (Var id) b ty alts)
421     else
422       return expr
423 -- Leave all other expressions unchanged
424 scrutsimpl c expr = return expr
425
426 --------------------------------
427 -- Scrutinee binder removal
428 --------------------------------
429 -- A case expression can have an extra binder, to which the scrutinee is bound
430 -- after bringing it to WHNF. This is used for forcing evaluation of strict
431 -- arguments. Since strictness does not matter for us (rather, everything is
432 -- sort of strict), this binder is ignored when generating VHDL, and must thus
433 -- be wild in the normal form.
434 scrutbndrremove :: Transform
435 -- If the scrutinee is already simple, and the bndr is not wild yet, replace
436 -- all occurences of the binder with the scrutinee variable.
437 scrutbndrremove c (Case (Var scrut) bndr ty alts) | bndr_used = do
438     alts' <- mapM subs_bndr alts
439     change $ Case (Var scrut) wild ty alts'
440   where
441     is_used (_, _, expr) = expr_uses_binders [bndr] expr
442     bndr_used = or $ map is_used alts
443     subs_bndr (con, bndrs, expr) = do
444       expr' <- substitute bndr (Var scrut) c expr
445       return (con, bndrs, expr')
446     wild = MkCore.mkWildBinder (Id.idType bndr)
447 -- Leave all other expressions unchanged
448 scrutbndrremove c expr = return expr
449
450 --------------------------------
451 -- Case normalization
452 --------------------------------
453 -- Turn a case expression with any number of alternatives with any
454 -- number of non-wild binders into as set of case and let expressions,
455 -- all of which are in normal form (e.g., a bunch of extractor case
456 -- expressions to extract all fields from the scrutinee, a number of let
457 -- bindings to bind each alternative and a single selector case to
458 -- select the right value.
459 casesimpl :: Transform
460 -- This is already a selector case (or, if x does not appear in bndrs, a very
461 -- simple case statement that will be removed by caseremove below). Just leave
462 -- it be.
463 casesimpl c expr@(Case scrut b ty [(con, bndrs, Var x)]) = return expr
464 -- Make sure that all case alternatives have only wild binders and simple
465 -- expressions.
466 -- This is done by creating a new let binding for each non-wild binder, which
467 -- is bound to a new simple selector case statement and for each complex
468 -- expression. We do this only for representable types, to prevent loops with
469 -- inlinenonrep.
470 casesimpl c expr@(Case scrut bndr ty alts) | not bndr_used = do
471   (bindingss, alts') <- (Monad.liftM unzip) $ mapM doalt alts
472   let bindings = concat bindingss
473   -- Replace the case with a let with bindings and a case
474   let newlet = mkNonRecLets bindings (Case scrut bndr ty alts')
475   -- If there are no non-wild binders, or this case is already a simple
476   -- selector (i.e., a single alt with exactly one binding), already a simple
477   -- selector altan no bindings (i.e., no wild binders in the original case),
478   -- don't change anything, otherwise, replace the case.
479   if null bindings then return expr else change newlet 
480   where
481   -- Check if the scrutinee binder is used
482   is_used (_, _, expr) = expr_uses_binders [bndr] expr
483   bndr_used = or $ map is_used alts
484   -- Generate a single wild binder, since they are all the same
485   wild = MkCore.mkWildBinder
486   -- Wilden the binders of one alt, producing a list of bindings as a
487   -- sideeffect.
488   doalt :: CoreAlt -> TransformMonad ([(CoreBndr, CoreExpr)], CoreAlt)
489   doalt (con, bndrs, expr) = do
490     -- Make each binder wild, if possible
491     bndrs_res <- Monad.zipWithM dobndr bndrs [0..]
492     let (newbndrs, bindings_maybe) = unzip bndrs_res
493     -- Extract a complex expression, if possible. For this we check if any of
494     -- the new list of bndrs are used by expr. We can't use free_vars here,
495     -- since that looks at the old bndrs.
496     let uses_bndrs = not $ VarSet.isEmptyVarSet $ CoreFVs.exprSomeFreeVars (`elem` newbndrs) expr
497     (exprbinding_maybe, expr') <- doexpr expr uses_bndrs
498     -- Create a new alternative
499     let newalt = (con, newbndrs, expr')
500     let bindings = Maybe.catMaybes (bindings_maybe ++ [exprbinding_maybe])
501     return (bindings, newalt)
502     where
503       -- Make wild alternatives for each binder
504       wildbndrs = map (\bndr -> MkCore.mkWildBinder (Id.idType bndr)) bndrs
505       -- A set of all the binders that are used by the expression
506       free_vars = CoreFVs.exprSomeFreeVars (`elem` bndrs) expr
507       -- Look at the ith binder in the case alternative. Return a new binder
508       -- for it (either the same one, or a wild one) and optionally a let
509       -- binding containing a case expression.
510       dobndr :: CoreBndr -> Int -> TransformMonad (CoreBndr, Maybe (CoreBndr, CoreExpr))
511       dobndr b i = do
512         repr <- isRepr b
513         -- Is b wild (e.g., not a free var of expr. Since b is only in scope
514         -- in expr, this means that b is unused if expr does not use it.)
515         let wild = not (VarSet.elemVarSet b free_vars)
516         -- Create a new binding for any representable binder that is not
517         -- already wild and is representable (to prevent loops with
518         -- inlinenonrep).
519         if (not wild) && repr
520           then do
521             caseexpr <- Trans.lift $ mkSelCase scrut i
522             -- Create a new binder that will actually capture a value in this
523             -- case statement, and return it.
524             return (wildbndrs!!i, Just (b, caseexpr))
525           else 
526             -- Just leave the original binder in place, and don't generate an
527             -- extra selector case.
528             return (b, Nothing)
529       -- Process the expression of a case alternative. Accepts an expression
530       -- and whether this expression uses any of the binders in the
531       -- alternative. Returns an optional new binding and a new expression.
532       doexpr :: CoreExpr -> Bool -> TransformMonad (Maybe (CoreBndr, CoreExpr), CoreExpr)
533       doexpr expr uses_bndrs = do
534         local_var <- Trans.lift $ is_local_var expr
535         repr <- isRepr expr
536         -- Extract any expressions that do not use any binders from this
537         -- alternative, is not a local var already and is representable (to
538         -- prevent loops with inlinenonrep).
539         if (not uses_bndrs) && (not local_var) && repr
540           then do
541             id <- Trans.lift $ mkBinderFor expr "caseval"
542             -- We don't flag a change here, since casevalsimpl will do that above
543             -- based on Just we return here.
544             return (Just (id, expr), Var id)
545           else
546             -- Don't simplify anything else
547             return (Nothing, expr)
548 -- Leave all other expressions unchanged
549 casesimpl c expr = return expr
550
551 --------------------------------
552 -- Case removal
553 --------------------------------
554 -- Remove case statements that have only a single alternative and only wild
555 -- binders.
556 caseremove :: Transform
557 -- Replace a useless case by the value of its single alternative
558 caseremove c (Case scrut b ty [(con, bndrs, expr)]) | not usesvars = change expr
559     -- Find if any of the binders are used by expr
560     where usesvars = (not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` b:bndrs))) expr
561 -- Leave all other expressions unchanged
562 caseremove c expr = return expr
563
564 --------------------------------
565 -- Case of known constructor simplification
566 --------------------------------
567 -- If a case expressions scrutinizes a datacon application, we can
568 -- determine which alternative to use and remove the case alltogether.
569 -- We replace it with a let expression the binds every binder in the
570 -- alternative bound to the corresponding argument of the datacon. We do
571 -- this instead of substituting the binders, to prevent duplication of
572 -- work and preserve sharing wherever appropriate.
573 knowncase :: Transform
574 knowncase context expr@(Case scrut@(App _ _) bndr ty alts) | not bndr_used = do
575     case collectArgs scrut of
576       (Var f, args) -> case Id.isDataConId_maybe f of
577         -- Not a dataconstructor? Don't change anything (probably a
578         -- function, then)
579         Nothing -> return expr
580         Just dc -> do
581           let (altcon, bndrs, res) =  case List.find (\(altcon, bndrs, res) -> altcon == (DataAlt dc)) alts of
582                 Just alt -> alt -- Return the alternative found
583                 Nothing -> head alts -- If the datacon is not present, the first must be the default alternative
584           -- Double check if we have either the correct alternative, or
585           -- the default.
586           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 ()
587           -- Find out how many arguments to drop (type variables and
588           -- predicates like dictionaries).
589           let (tvs, preds, _, _) = DataCon.dataConSig dc
590           let count = length tvs + length preds
591           -- Create a let expression that binds each of the binders in
592           -- this alternative to the corresponding argument of the data
593           -- constructor.
594           let binds = zip bndrs (drop count args)
595           change $ Let (Rec binds) res
596       _ -> return expr -- Scrutinee is not an application of a var
597   where
598     is_used (_, _, expr) = expr_uses_binders [bndr] expr
599     bndr_used = or $ map is_used alts
600
601 -- Leave all other expressions unchanged
602 knowncase c expr = return expr
603
604
605
606
607 ----------------------------------------------------------------
608 -- Unrepresentable value removal transformations
609 ----------------------------------------------------------------
610
611 --------------------------------
612 -- Non-representable binding inlining
613 --------------------------------
614 -- Remove a = B bindings, with B of a non-representable type, from let
615 -- expressions everywhere. This means that any value that we can't generate a
616 -- signal for, will be inlined and hopefully turned into something we can
617 -- represent.
618 --
619 -- This is a tricky function, which is prone to create loops in the
620 -- transformations. To fix this, we make sure that no transformation will
621 -- create a new let binding with a non-representable type. These other
622 -- transformations will just not work on those function-typed values at first,
623 -- but the other transformations (in particular β-reduction) should make sure
624 -- that the type of those values eventually becomes representable.
625 inlinenonrep :: Transform
626 inlinenonrep = inlinebind ((Monad.liftM not) . isRepr . snd)
627
628 --------------------------------
629 -- Function specialization
630 --------------------------------
631 -- Remove all applications to non-representable arguments, by duplicating the
632 -- function called with the non-representable parameter replaced by the free
633 -- variables of the argument passed in.
634 argprop :: Transform
635 -- Transform any application of a named function (i.e., skip applications of
636 -- lambda's). Also skip applications that have arguments with free type
637 -- variables, since we can't inline those.
638 argprop c expr@(App _ _) | is_var fexpr = do
639   -- Find the body of the function called
640   body_maybe <- Trans.lift $ getGlobalBind f
641   case body_maybe of
642     Just body -> do
643       -- Process each of the arguments in turn
644       (args', changed) <- Writer.listen $ mapM doarg args
645       -- See if any of the arguments changed
646       case Monoid.getAny changed of
647         True -> do
648           let (newargs', newparams', oldargs) = unzip3 args'
649           let newargs = concat newargs'
650           let newparams = concat newparams'
651           -- Create a new body that consists of a lambda for all new arguments and
652           -- the old body applied to some arguments.
653           let newbody = MkCore.mkCoreLams newparams (MkCore.mkCoreApps body oldargs)
654           -- Create a new function with the same name but a new body
655           newf <- Trans.lift $ mkFunction f newbody
656
657           Trans.lift $ MonadState.modify tsInitStates (\ismap ->
658             let init_state_maybe = Map.lookup f ismap in
659             case init_state_maybe of
660               Nothing -> ismap
661               Just init_state -> Map.insert newf init_state ismap)
662           -- Replace the original application with one of the new function to the
663           -- new arguments.
664           change $ MkCore.mkCoreApps (Var newf) newargs
665         False ->
666           -- Don't change the expression if none of the arguments changed
667           return expr
668       
669     -- If we don't have a body for the function called, leave it unchanged (it
670     -- should be a primitive function then).
671     Nothing -> return expr
672   where
673     -- Find the function called and the arguments
674     (fexpr, args) = collectArgs expr
675     Var f = fexpr
676
677     -- Process a single argument and return (args, bndrs, arg), where args are
678     -- the arguments to replace the given argument in the original
679     -- application, bndrs are the binders to include in the top-level lambda
680     -- in the new function body, and arg is the argument to apply to the old
681     -- function body.
682     doarg :: CoreExpr -> TransformMonad ([CoreExpr], [CoreBndr], CoreExpr)
683     doarg arg = do
684       repr <- isRepr arg
685       bndrs <- Trans.lift getGlobalBinders
686       let interesting var = Var.isLocalVar var && (var `notElem` bndrs)
687       if not repr && not (is_var arg && interesting (exprToVar arg)) && not (has_free_tyvars arg) 
688         then do
689           -- Propagate all complex arguments that are not representable, but not
690           -- arguments with free type variables (since those would require types
691           -- not known yet, which will always be known eventually).
692           -- Find interesting free variables, each of which should be passed to
693           -- the new function instead of the original function argument.
694           -- 
695           -- Interesting vars are those that are local, but not available from the
696           -- top level scope (functions from this module are defined as local, but
697           -- they're not local to this function, so we can freely move references
698           -- to them into another function).
699           let free_vars = VarSet.varSetElems $ CoreFVs.exprSomeFreeVars interesting arg
700           -- Mark the current expression as changed
701           setChanged
702           -- TODO: Clone the free_vars (and update references in arg), since
703           -- this might cause conflicts if two arguments that are propagated
704           -- share a free variable. Also, we are now introducing new variables
705           -- into a function that are not fresh, which violates the binder
706           -- uniqueness invariant.
707           return (map Var free_vars, free_vars, arg)
708         else do
709           -- Representable types will not be propagated, and arguments with free
710           -- type variables will be propagated later.
711           -- Note that we implicitly remove any type variables in the type of
712           -- the original argument by using the type of the actual argument
713           -- for the new formal parameter.
714           -- TODO: preserve original naming?
715           id <- Trans.lift $ mkBinderFor arg "param"
716           -- Just pass the original argument to the new function, which binds it
717           -- to a new id and just pass that new id to the old function body.
718           return ([arg], [id], mkReferenceTo id) 
719 -- Leave all other expressions unchanged
720 argprop c expr = return expr
721
722 --------------------------------
723 -- Non-representable result inlining
724 --------------------------------
725 -- This transformation takes a function (top level binding) that has a
726 -- non-representable result (e.g., a tuple containing a function, or an
727 -- Integer. The latter can occur in some cases as the result of the
728 -- fromIntegerT function) and inlines enough of the function to make the
729 -- result representable again.
730 --
731 -- This is done by first normalizing the function and then "inlining"
732 -- the result. Since no unrepresentable let bindings are allowed in
733 -- normal form, we can be sure that all free variables of the result
734 -- expression will be representable (Note that we probably can't
735 -- guarantee that all representable parts of the expression will be free
736 -- variables, so we might inline more than strictly needed).
737 --
738 -- The new function result will be a tuple containing all free variables
739 -- of the old result, so the old result can be rebuild at the caller.
740 --
741 -- We take care not to inline dictionary id's, which are top level
742 -- bindings with a non-representable result type as well, since those
743 -- will never become VHDL signals directly. There is a separate
744 -- transformation (inlinedict) that specifically inlines dictionaries
745 -- only when it is useful.
746 inlinenonrepresult :: Transform
747
748 -- Apply to any (application of) a reference to a top level function
749 -- that is fully applied (i.e., dos not have a function type) but is not
750 -- representable. We apply in any context, since non-representable
751 -- expressions are generally left alone and can occur anywhere.
752 inlinenonrepresult context expr | not (is_fun expr) =
753   case collectArgs expr of
754     (Var f, args) | not (Id.isDictId f) -> do
755       repr <- isRepr expr
756       if not repr
757         then do
758           body_maybe <- Trans.lift $ getNormalized_maybe True f
759           case body_maybe of
760             Just body -> do
761               let (bndrs, binds, res) = splitNormalizedNonRep body
762               if has_free_tyvars res 
763                 then
764                   -- Don't touch anything with free type variables, since
765                   -- we can't return those. We'll wait until argprop
766                   -- removed those variables.
767                   return expr
768                 else do
769                   -- Get the free local variables of res
770                   global_bndrs <- Trans.lift getGlobalBinders
771                   let interesting var = Var.isLocalVar var && (var `notElem` global_bndrs)
772                   let free_vars = VarSet.varSetElems $ CoreFVs.exprSomeFreeVars interesting res
773                   let free_var_types = map Id.idType free_vars
774                   let n_free_vars = length free_vars
775                   -- Get a tuple datacon to wrap around the free variables
776                   let fvs_datacon = TysWiredIn.tupleCon BasicTypes.Boxed n_free_vars
777                   let fvs_datacon_id = DataCon.dataConWorkId fvs_datacon
778                   -- Let the function now return a tuple with references to
779                   -- all free variables of the old return value. First pass
780                   -- all the types of the variables, since tuple
781                   -- constructors are polymorphic.
782                   let newres = mkApps (Var fvs_datacon_id) (map Type free_var_types ++  map Var free_vars)
783                   -- Recreate the function body with the changed return value
784                   let newbody = mkLams bndrs (Let (Rec binds) newres) 
785                   -- Create the new function
786                   f' <- Trans.lift $ mkFunction f newbody
787
788                   -- Call the new function
789                   let newapp = mkApps (Var f') args
790                   res_bndr <- Trans.lift $ mkBinderFor newapp "res"
791                   -- Create extractor case expressions to extract each of the
792                   -- free variables from the tuple.
793                   sel_cases <- Trans.lift $ mapM (mkSelCase (Var res_bndr)) [0..n_free_vars-1]
794
795                   -- Bind the res_bndr to the result of the new application
796                   -- and each of the free variables to the corresponding
797                   -- selector case. Replace the let body with the original
798                   -- body of the called function (which can still access all
799                   -- of its free variables, from the let).
800                   let binds = (res_bndr, newapp):(zip free_vars sel_cases)
801                   let letexpr = Let (Rec binds) res
802
803                   -- Finally, regenarate all uniques in the new expression,
804                   -- since the free variables could otherwise become
805                   -- duplicated. It is not strictly necessary to regenerate
806                   -- res, since we're moving that expression, but it won't
807                   -- hurt.
808                   letexpr_uniqued <- Trans.lift $ genUniques letexpr
809                   change letexpr_uniqued
810             Nothing -> return expr
811         else
812           -- Don't touch representable expressions or (applications of)
813           -- dictionary ids.
814           return expr
815     -- Not a reference to or application of a top level function
816     _ -> return expr
817 -- Leave all other expressions unchanged
818 inlinenonrepresult c expr = return expr
819
820 ----------------------------------------------------------------
821 -- Type-class transformations
822 ----------------------------------------------------------------
823
824 --------------------------------
825 -- ClassOp resolution
826 --------------------------------
827 -- Resolves any class operation to the actual operation whenever
828 -- possible. Class methods (as well as parent dictionary selectors) are
829 -- special "functions" that take a type and a dictionary and evaluate to
830 -- the corresponding method. A dictionary is nothing more than a
831 -- special dataconstructor applied to the type the dictionary is for,
832 -- each of the superclasses and all of the class method definitions for
833 -- that particular type. Since dictionaries all always inlined (top
834 -- levels dictionaries are inlined by inlinedict, local dictionaries are
835 -- inlined by inlinenonrep), we will eventually have something like:
836 --
837 --   baz
838 --     @ CLasH.HardwareTypes.Bit
839 --     (D:Baz @ CLasH.HardwareTypes.Bit bitbaz)
840 --
841 -- Here, baz is the method selector for the baz method, while
842 -- D:Baz is the dictionary constructor for the Baz and bitbaz is the baz
843 -- method defined in the Baz Bit instance declaration.
844 --
845 -- To resolve this, we can look at the ClassOp IdInfo from the baz Id,
846 -- which contains the Class it is defined for. From the Class, we can
847 -- get a list of all selectors (both parent class selectors as well as
848 -- method selectors). Since the arguments to D:Baz (after the type
849 -- argument) correspond exactly to this list, we then look up baz in
850 -- that list and replace the entire expression by the corresponding 
851 -- argument to D:Baz.
852 --
853 -- We don't resolve methods that have a builtin translation (such as
854 -- ==), since the actual implementation is not always (easily)
855 -- translateable. For example, when deriving ==, GHC generates code
856 -- using $con2tag functions to translate a datacon to an int and compare
857 -- that with GHC.Prim.==# . Better to avoid that for now.
858 classopresolution :: Transform
859 classopresolution c expr@(App (App (Var sel) ty) dict) | not is_builtin =
860   case Id.isClassOpId_maybe sel of
861     -- Not a class op selector
862     Nothing -> return expr
863     Just cls -> case collectArgs dict of
864       (_, []) -> return expr -- Dict is not an application (e.g., not inlined yet)
865       (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)
866                                 | tyargs_neq ty ty' -> error $ "Normalize.classopresolution: Applying class selector to dictionary without matching type?\n" ++ pprString expr
867                                 | otherwise ->
868         let selector_ids = Class.classSelIds cls in
869         -- Find the selector used in the class' list of selectors
870         case List.elemIndex sel selector_ids of
871           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
872           -- Get the corresponding argument from the dictionary
873           Just n -> change (selectors!!n)
874       (_, _) -> return expr -- Not applying a variable? Don't touch
875   where
876     -- Compare two type arguments, returning True if they are _not_
877     -- equal
878     tyargs_neq (Type ty1) (Type ty2) = not $ Type.coreEqType ty1 ty2
879     tyargs_neq _ _ = True
880     -- Is this a builtin function / method?
881     is_builtin = elem (Name.getOccString sel) builtinIds
882
883 -- Leave all other expressions unchanged
884 classopresolution c expr = return expr
885
886 --------------------------------
887 -- Dictionary inlining
888 --------------------------------
889 -- Inline all top level dictionaries, that are in a position where
890 -- classopresolution can actually resolve them. This makes this
891 -- transformation look similar to classoperesolution below, but we'll
892 -- keep them separated for clarity. By not inlining other dictionaries,
893 -- we prevent expression sizes exploding when huge type level integer
894 -- dictionaries are inlined which can never be expanded (in casts, for
895 -- example).
896 inlinedict c expr@(App (App (Var sel) ty) (Var dict)) | not is_builtin && is_classop = do
897   body_maybe <- Trans.lift $ getGlobalBind dict
898   case body_maybe of
899     -- No body available (no source available, or a local variable /
900     -- argument)
901     Nothing -> return expr
902     Just body -> change (App (App (Var sel) ty) body)
903   where
904     -- Is this a builtin function / method?
905     is_builtin = elem (Name.getOccString sel) builtinIds
906     -- Are we dealing with a class operation selector?
907     is_classop = Maybe.isJust (Id.isClassOpId_maybe sel)
908
909 -- Leave all other expressions unchanged
910 inlinedict c expr = return expr
911
912
913 {-
914 --------------------------------
915 -- Identical let binding merging
916 --------------------------------
917 -- Merge two bindings in a let if they are identical 
918 -- TODO: We would very much like to use GHC's CSE module for this, but that
919 -- doesn't track if something changed or not, so we can't use it properly.
920 letmerge :: Transform
921 letmerge c expr@(Let _ _) = do
922   let (binds, res) = flattenLets expr
923   binds' <- domerge binds
924   return $ mkNonRecLets binds' res
925   where
926     domerge :: [(CoreBndr, CoreExpr)] -> TransformMonad [(CoreBndr, CoreExpr)]
927     domerge [] = return []
928     domerge (e:es) = do 
929       es' <- mapM (mergebinds e) es
930       es'' <- domerge es'
931       return (e:es'')
932
933     -- Uses the second bind to simplify the second bind, if applicable.
934     mergebinds :: (CoreBndr, CoreExpr) -> (CoreBndr, CoreExpr) -> TransformMonad (CoreBndr, CoreExpr)
935     mergebinds (b1, e1) (b2, e2)
936       -- Identical expressions? Replace the second binding with a reference to
937       -- the first binder.
938       | CoreUtils.cheapEqExpr e1 e2 = change $ (b2, Var b1)
939       -- Different expressions? Don't change
940       | otherwise = return (b2, e2)
941 -- Leave all other expressions unchanged
942 letmerge c expr = return expr
943 -}
944
945 --------------------------------
946 -- End of transformations
947 --------------------------------
948
949
950
951
952 -- What transforms to run?
953 transforms = [ ("inlinedict", inlinedict)
954              , ("inlinetoplevel", inlinetoplevel)
955              , ("inlinenonrepresult", inlinenonrepresult)
956              , ("knowncase", knowncase)
957              , ("classopresolution", classopresolution)
958              , ("argprop", argprop)
959              , ("funextract", funextract)
960              , ("eta", eta)
961              , ("beta", beta)
962              , ("appprop", appprop)
963              , ("castprop", castprop)
964              , ("letremovesimple", letremovesimple)
965              , ("letrec", letrec)
966              , ("letremove", letremove)
967              , ("retvalsimpl", retvalsimpl)
968              , ("letflat", letflat)
969              , ("scrutsimpl", scrutsimpl)
970              , ("scrutbndrremove", scrutbndrremove)
971              , ("casesimpl", casesimpl)
972              , ("caseremove", caseremove)
973              , ("inlinenonrep", inlinenonrep)
974              , ("appsimpl", appsimpl)
975              , ("letremoveunused", letremoveunused)
976              , ("castsimpl", castsimpl)
977              ]
978
979 -- | Returns the normalized version of the given function, or an error
980 -- if it is not a known global binder.
981 getNormalized ::
982   Bool -- ^ Allow the result to be unrepresentable?
983   -> CoreBndr -- ^ The function to get
984   -> TranslatorSession CoreExpr -- The normalized function body
985 getNormalized result_nonrep bndr = do
986   norm <- getNormalized_maybe result_nonrep bndr
987   return $ Maybe.fromMaybe
988     (error $ "Normalize.getNormalized: Unknown or non-representable function requested: " ++ show bndr)
989     norm
990
991 -- | Returns the normalized version of the given function, or Nothing
992 -- when the binder is not a known global binder or is not normalizeable.
993 getNormalized_maybe ::
994   Bool -- ^ Allow the result to be unrepresentable?
995   -> CoreBndr -- ^ The function to get
996   -> TranslatorSession (Maybe CoreExpr) -- The normalized function body
997
998 getNormalized_maybe result_nonrep bndr = do
999     expr_maybe <- getGlobalBind bndr
1000     normalizeable <- isNormalizeable result_nonrep bndr
1001     if not normalizeable || Maybe.isNothing expr_maybe
1002       then
1003         -- Binder not normalizeable or not found
1004         return Nothing
1005       else do
1006         -- Binder found and is monomorphic. Normalize the expression
1007         -- and cache the result.
1008         normalized <- Utils.makeCached bndr tsNormalized $ 
1009           normalizeExpr (show bndr) (Maybe.fromJust expr_maybe)
1010         return (Just normalized)
1011
1012 -- | Normalize an expression
1013 normalizeExpr ::
1014   String -- ^ What are we normalizing? For debug output only.
1015   -> CoreSyn.CoreExpr -- ^ The expression to normalize 
1016   -> TranslatorSession CoreSyn.CoreExpr -- ^ The normalized expression
1017
1018 normalizeExpr what expr = do
1019       startcount <- MonadState.get tsTransformCounter 
1020       expr_uniqued <- genUniques expr
1021       -- Do a debug print, if requested
1022       let expr_uniqued' = Utils.traceIf (normalize_debug >= NormDbgFinal) (what ++ " before normalization:\n\n" ++ showSDoc ( ppr expr_uniqued ) ++ "\n") expr_uniqued
1023       -- Normalize this expression
1024       expr' <- dotransforms transforms expr_uniqued'
1025       endcount <- MonadState.get tsTransformCounter 
1026       -- Do a debug print, if requested
1027       Utils.traceIf (normalize_debug >= NormDbgFinal)  (what ++ " after normalization:\n\n" ++ showSDoc ( ppr expr') ++ "\nNeeded " ++ show (endcount - startcount) ++ " transformations to normalize " ++ what) $
1028         return expr'
1029
1030 -- | Split a normalized expression into the argument binders, top level
1031 --   bindings and the result binder. This function returns an error if
1032 --   the type of the expression is not representable.
1033 splitNormalized ::
1034   CoreExpr -- ^ The normalized expression
1035   -> ([CoreBndr], [Binding], CoreBndr)
1036 splitNormalized expr = 
1037   case splitNormalizedNonRep expr of
1038     (args, binds, Var res) -> (args, binds, res)
1039     _ -> error $ "Normalize.splitNormalized: Not in normal form: " ++ pprString expr ++ "\n"
1040
1041 -- Split a normalized expression, whose type can be unrepresentable.
1042 splitNormalizedNonRep::
1043   CoreExpr -- ^ The normalized expression
1044   -> ([CoreBndr], [Binding], CoreExpr)
1045 splitNormalizedNonRep expr = (args, binds, resexpr)
1046   where
1047     (args, letexpr) = CoreSyn.collectBinders expr
1048     (binds, resexpr) = flattenLets letexpr