c27e93eb7803c0c4604492308cbccd9fadbc2864
[matthijs/master-project/cλash.git] / clash / CLasH / Normalize.hs
1 --
2 -- Functions to bring a Core expression in normal form. This module provides a
3 -- top level function "normalize", and defines the actual transformation passes that
4 -- are performed.
5 --
6 module CLasH.Normalize (getNormalized, normalizeExpr, splitNormalized) where
7
8 -- Standard modules
9 import Debug.Trace
10 import qualified Maybe
11 import qualified List
12 import qualified Control.Monad.Trans.Class as Trans
13 import qualified Control.Monad as Monad
14 import qualified Control.Monad.Trans.Writer as Writer
15 import qualified Data.Accessor.Monad.Trans.State as MonadState
16 import qualified Data.Monoid as Monoid
17 import qualified Data.Map as Map
18
19 -- GHC API
20 import CoreSyn
21 import qualified CoreUtils
22 import qualified BasicTypes
23 import qualified Type
24 import qualified TysWiredIn
25 import qualified Id
26 import qualified Var
27 import qualified Name
28 import qualified DataCon
29 import qualified VarSet
30 import qualified CoreFVs
31 import qualified Class
32 import qualified MkCore
33 import Outputable ( showSDoc, ppr, nest )
34
35 -- Local imports
36 import CLasH.Normalize.NormalizeTypes
37 import CLasH.Translator.TranslatorTypes
38 import CLasH.Normalize.NormalizeTools
39 import CLasH.VHDL.Constants (builtinIds)
40 import qualified CLasH.Utils as Utils
41 import CLasH.Utils.Core.CoreTools
42 import CLasH.Utils.Core.BinderTools
43 import CLasH.Utils.Pretty
44
45 ----------------------------------------------------------------
46 -- Cleanup transformations
47 ----------------------------------------------------------------
48
49 --------------------------------
50 -- β-reduction
51 --------------------------------
52 beta :: Transform
53 -- Substitute arg for x in expr. For value lambda's, also clone before
54 -- substitution.
55 beta c (App (Lam x expr) arg) | CoreSyn.isTyVar x = setChanged >> substitute x arg c expr
56                               | otherwise         = setChanged >> substitute_clone x arg c expr
57 -- Leave all other expressions unchanged
58 beta c expr = return expr
59
60 --------------------------------
61 -- Unused let binding removal
62 --------------------------------
63 letremoveunused :: Transform
64 letremoveunused c expr@(Let (NonRec b bound) res) = do
65   let used = expr_uses_binders [b] res
66   if used
67     then return expr
68     else change res
69 letremoveunused c expr@(Let (Rec binds) res) = do
70   -- Filter out all unused binds.
71   let binds' = filter dobind binds
72   -- Only set the changed flag if binds got removed
73   changeif (length binds' /= length binds) (Let (Rec binds') res)
74     where
75       bound_exprs = map snd binds
76       -- For each bind check if the bind is used by res or any of the bound
77       -- expressions
78       dobind (bndr, _) = any (expr_uses_binders [bndr]) (res:bound_exprs)
79 -- Leave all other expressions unchanged
80 letremoveunused c expr = return expr
81
82 --------------------------------
83 -- empty let removal
84 --------------------------------
85 -- Remove empty (recursive) lets
86 letremove :: Transform
87 letremove c (Let (Rec []) res) = change res
88 -- Leave all other expressions unchanged
89 letremove c expr = return expr
90
91 --------------------------------
92 -- Simple let binding removal
93 --------------------------------
94 -- Remove a = b bindings from let expressions everywhere
95 letremovesimple :: Transform
96 letremovesimple = inlinebind (\(b, e) -> Trans.lift $ is_local_var e)
97
98 --------------------------------
99 -- Cast propagation
100 --------------------------------
101 -- Try to move casts as much downward as possible.
102 castprop :: Transform
103 castprop c (Cast (Let binds expr) ty) = change $ Let binds (Cast expr ty)
104 castprop c expr@(Cast (Case scrut b _ alts) ty) = change (Case scrut b ty alts')
105   where
106     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (Cast expr ty))) alts
107 -- Leave all other expressions unchanged
108 castprop c expr = return expr
109
110 --------------------------------
111 -- Cast simplification. Mostly useful for state packing and unpacking, but
112 -- perhaps for others as well.
113 --------------------------------
114 castsimpl :: Transform
115 castsimpl c expr@(Cast val ty) = do
116   -- Don't extract values that are already simpl
117   local_var <- Trans.lift $ is_local_var val
118   -- Don't extract values that are not representable, to prevent loops with
119   -- inlinenonrep
120   repr <- isRepr val
121   if (not local_var) && repr
122     then do
123       -- Generate a binder for the expression
124       id <- Trans.lift $ mkBinderFor val "castval"
125       -- Extract the expression
126       change $ Let (NonRec id val) (Cast (Var id) ty)
127     else
128       return expr
129 -- Leave all other expressions unchanged
130 castsimpl c expr = return expr
131
132 --------------------------------
133 -- Top level function inlining
134 --------------------------------
135 -- This transformation inlines simple top level bindings. Simple
136 -- currently means that the body is only a single application (though
137 -- the complexity of the arguments is not currently checked) or that the
138 -- normalized form only contains a single binding. This should catch most of the
139 -- cases where a top level function is created that simply calls a type class
140 -- method with a type and dictionary argument, e.g.
141 --   fromInteger = GHC.Num.fromInteger (SizedWord D8) $dNum
142 -- which is later called using simply
143 --   fromInteger (smallInteger 10)
144 --
145 -- These useless wrappers are created by GHC automatically. If we don't
146 -- inline them, we get loads of useless components cluttering the
147 -- generated VHDL.
148 --
149 -- Note that the inlining could also inline simple functions defined by
150 -- the user, not just GHC generated functions. It turns out to be near
151 -- impossible to reliably determine what functions are generated and
152 -- what functions are user-defined. Instead of guessing (which will
153 -- inline less than we want) we will just inline all simple functions.
154 --
155 -- Only functions that are actually completely applied and bound by a
156 -- variable in a let expression are inlined. These are the expressions
157 -- that will eventually generate instantiations of trivial components.
158 -- By not inlining any other reference, we also prevent looping problems
159 -- with funextract and inlinedict.
160 inlinetoplevel :: Transform
161 inlinetoplevel (LetBinding:_) expr | not (is_fun expr) =
162   case collectArgs expr of
163         (Var f, args) -> do
164           body_maybe <- needsInline f
165           case body_maybe of
166                 Just body -> do
167                         -- Regenerate all uniques in the to-be-inlined expression
168                         body_uniqued <- Trans.lift $ genUniques body
169                         -- And replace the variable reference with the unique'd body.
170                         change (mkApps body_uniqued args)
171                         -- No need to inline
172                 Nothing -> return expr
173         -- This is not an application of a binder, leave it unchanged.
174         _ -> return expr
175
176 -- Leave all other expressions unchanged
177 inlinetoplevel c expr = return expr
178
179 -- | Does the given binder need to be inlined? If so, return the body to
180 -- be used for inlining.
181 needsInline :: CoreBndr -> TransformMonad (Maybe CoreExpr)
182 needsInline f = do
183   body_maybe <- Trans.lift $ getGlobalBind f
184   case body_maybe of
185     -- No body available?
186     Nothing -> return Nothing
187     Just body -> case CoreSyn.collectArgs body of
188       -- The body is some (top level) binder applied to 0 or more
189       -- arguments. That should be simple enough to inline.
190       (Var f, args) -> return $ Just body
191       -- Body is more complicated, try normalizing it
192       _ -> do
193         norm_maybe <- Trans.lift $ getNormalized_maybe False f
194         case norm_maybe of
195           -- Noth normalizeable
196           Nothing -> return Nothing 
197           Just norm -> case splitNormalizedNonRep norm of
198             -- The function has just a single binding, so that's simple
199             -- enough to inline.
200             (args, [bind], Var res) -> return $ Just norm
201             -- More complicated function, don't inline
202             _ -> return Nothing
203
204
205 ----------------------------------------------------------------
206 -- Program structure transformations
207 ----------------------------------------------------------------
208
209 --------------------------------
210 -- η expansion
211 --------------------------------
212 -- Make sure all parameters to the normalized functions are named by top
213 -- level lambda expressions. For this we apply η expansion to the
214 -- function body (possibly enclosed in some lambda abstractions) while
215 -- it has a function type. Eventually this will result in a function
216 -- body consisting of a bunch of nested lambdas containing a
217 -- non-function value (e.g., a complete application).
218 eta :: Transform
219 eta c expr | is_fun expr && not (is_lam expr) && all (== LambdaBody) c = do
220   let arg_ty = (fst . Type.splitFunTy . CoreUtils.exprType) expr
221   id <- Trans.lift $ mkInternalVar "param" arg_ty
222   change (Lam id (App expr (Var id)))
223 -- Leave all other expressions unchanged
224 eta c e = return e
225
226 --------------------------------
227 -- Application propagation
228 --------------------------------
229 -- Move applications into let and case expressions.
230 appprop :: Transform
231 -- Propagate the application into the let
232 appprop c (App (Let binds expr) arg) = change $ Let binds (App expr arg)
233 -- Propagate the application into each of the alternatives
234 appprop c (App (Case scrut b ty alts) arg) = change $ Case scrut b ty' alts'
235   where 
236     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (App expr arg))) alts
237     ty' = CoreUtils.applyTypeToArg ty arg
238 -- Leave all other expressions unchanged
239 appprop c expr = return expr
240
241 --------------------------------
242 -- Let recursification
243 --------------------------------
244 -- Make all lets recursive, so other transformations don't need to
245 -- handle non-recursive lets
246 letrec :: Transform
247 letrec c expr@(Let (NonRec bndr val) res) = 
248   change $ Let (Rec [(bndr, val)]) res
249
250 -- Leave all other expressions unchanged
251 letrec c expr = return expr
252
253 --------------------------------
254 -- let flattening
255 --------------------------------
256 -- Takes a let that binds another let, and turns that into two nested lets.
257 -- e.g., from:
258 -- let b = (let b' = expr' in res') in res
259 -- to:
260 -- let b' = expr' in (let b = res' in res)
261 letflat :: Transform
262 -- Turn a nonrec let that binds a let into two nested lets.
263 letflat c (Let (NonRec b (Let binds  res')) res) = 
264   change $ Let binds (Let (NonRec b res') res)
265 letflat c (Let (Rec binds) expr) = do
266   -- Flatten each binding.
267   binds' <- Utils.concatM $ Monad.mapM flatbind binds
268   -- Return the new let. We don't use change here, since possibly nothing has
269   -- changed. If anything has changed, flatbind has already flagged that
270   -- change.
271   return $ Let (Rec binds') expr
272   where
273     -- Turns a binding of a let into a multiple bindings, or any other binding
274     -- into a list with just that binding
275     flatbind :: (CoreBndr, CoreExpr) -> TransformMonad [(CoreBndr, CoreExpr)]
276     flatbind (b, Let (Rec binds) expr) = change ((b, expr):binds)
277     flatbind (b, Let (NonRec b' expr') expr) = change [(b, expr), (b', expr')]
278     flatbind (b, expr) = return [(b, expr)]
279 -- Leave all other expressions unchanged
280 letflat c expr = return expr
281
282 --------------------------------
283 -- Return value simplification
284 --------------------------------
285 -- Ensure the return value of a function follows proper normal form. eta
286 -- expansion ensures the body starts with lambda abstractions, this
287 -- transformation ensures that the lambda abstractions always contain a
288 -- recursive let and that, when the return value is representable, the
289 -- let contains a local variable reference in its body.
290
291 -- Extract the return value from the body of the top level lambdas (of
292 -- which ther could be zero), unless it is a let expression (in which
293 -- case the next clause applies).
294 retvalsimpl c expr | all (== LambdaBody) c && not (is_lam expr) && not (is_let expr) = do
295   local_var <- Trans.lift $ is_local_var expr
296   repr <- isRepr expr
297   if not local_var && repr
298     then do
299       id <- Trans.lift $ mkBinderFor expr "res" 
300       change $ Let (Rec [(id, expr)]) (Var id)
301     else
302       return expr
303 -- Extract the return value from the body of a let expression, which is
304 -- itself the body of the top level lambdas (of which there could be
305 -- zero).
306 retvalsimpl c expr@(Let (Rec binds) body) | all (== LambdaBody) c = do
307   -- Don't extract values that are already a local variable, to prevent
308   -- loops with ourselves.
309   local_var <- Trans.lift $ is_local_var body
310   -- Don't extract values that are not representable, to prevent loops with
311   -- inlinenonrep
312   repr <- isRepr body
313   if not local_var && repr
314     then do
315       id <- Trans.lift $ mkBinderFor body "res" 
316       change $ Let (Rec ((id, body):binds)) (Var id)
317     else
318       return expr
319 -- Leave all other expressions unchanged
320 retvalsimpl c expr = return expr
321
322 --------------------------------
323 -- Representable arguments simplification
324 --------------------------------
325 -- Make sure that all arguments of a representable type are simple variables.
326 appsimpl :: Transform
327 -- Simplify all representable arguments. Do this by introducing a new Let
328 -- that binds the argument and passing the new binder in the application.
329 appsimpl c expr@(App f arg) = do
330   -- Check runtime representability
331   repr <- isRepr arg
332   local_var <- Trans.lift $ is_local_var arg
333   if repr && not local_var
334     then do -- Extract representable arguments
335       id <- Trans.lift $ mkBinderFor arg "arg"
336       change $ Let (NonRec id arg) (App f (Var id))
337     else -- Leave non-representable arguments unchanged
338       return expr
339 -- Leave all other expressions unchanged
340 appsimpl c expr = return expr
341
342 ----------------------------------------------------------------
343 -- Built-in function transformations
344 ----------------------------------------------------------------
345
346 --------------------------------
347 -- Function-typed argument extraction
348 --------------------------------
349 -- This transform takes any function-typed argument that cannot be propagated
350 -- (because the function that is applied to it is a builtin function), and
351 -- puts it in a brand new top level binder. This allows us to for example
352 -- apply map to a lambda expression This will not conflict with inlinenonrep,
353 -- since that only inlines local let bindings, not top level bindings.
354 funextract :: Transform
355 funextract c expr@(App _ _) | is_var fexpr = do
356   body_maybe <- Trans.lift $ getGlobalBind f
357   case body_maybe of
358     -- We don't have a function body for f, so we can perform this transform.
359     Nothing -> do
360       -- Find the new arguments
361       args' <- mapM doarg args
362       -- And update the arguments. We use return instead of changed, so the
363       -- changed flag doesn't get set if none of the args got changed.
364       return $ MkCore.mkCoreApps fexpr args'
365     -- We have a function body for f, leave this application to funprop
366     Just _ -> return expr
367   where
368     -- Find the function called and the arguments
369     (fexpr, args) = collectArgs expr
370     Var f = fexpr
371     -- Change any arguments that have a function type, but are not simple yet
372     -- (ie, a variable or application). This means to create a new function
373     -- for map (\f -> ...) b, but not for map (foo a) b.
374     --
375     -- We could use is_applicable here instead of is_fun, but I think
376     -- arguments to functions could only have forall typing when existential
377     -- typing is enabled. Not sure, though.
378     doarg arg | not (is_simple arg) && is_fun arg = do
379       -- Create a new top level binding that binds the argument. Its body will
380       -- be extended with lambda expressions, to take any free variables used
381       -- by the argument expression.
382       let free_vars = VarSet.varSetElems $ CoreFVs.exprFreeVars arg
383       let body = MkCore.mkCoreLams free_vars arg
384       id <- Trans.lift $ mkBinderFor body "fun"
385       Trans.lift $ addGlobalBind id body
386       -- Replace the argument with a reference to the new function, applied to
387       -- all vars it uses.
388       change $ MkCore.mkCoreApps (Var id) (map Var free_vars)
389     -- Leave all other arguments untouched
390     doarg arg = return arg
391
392 -- Leave all other expressions unchanged
393 funextract c expr = return expr
394
395
396
397
398 ----------------------------------------------------------------
399 -- Case normalization transformations
400 ----------------------------------------------------------------
401
402 --------------------------------
403 -- Scrutinee simplification
404 --------------------------------
405 -- Make sure the scrutinee of a case expression is a local variable
406 -- reference.
407 scrutsimpl :: Transform
408 -- Don't touch scrutinees that are already simple
409 scrutsimpl c expr@(Case (Var _) _ _ _) = return expr
410 -- Replace all other cases with a let that binds the scrutinee and a new
411 -- simple scrutinee, but only when the scrutinee is representable (to prevent
412 -- loops with inlinenonrep, though I don't think a non-representable scrutinee
413 -- will be supported anyway...) 
414 scrutsimpl c expr@(Case scrut b ty alts) = do
415   repr <- isRepr scrut
416   if repr
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 -- ClassOp resolution
821 --------------------------------
822 -- Resolves any class operation to the actual operation whenever
823 -- possible. Class methods (as well as parent dictionary selectors) are
824 -- special "functions" that take a type and a dictionary and evaluate to
825 -- the corresponding method. A dictionary is nothing more than a
826 -- special dataconstructor applied to the type the dictionary is for,
827 -- each of the superclasses and all of the class method definitions for
828 -- that particular type. Since dictionaries all always inlined (top
829 -- levels dictionaries are inlined by inlinedict, local dictionaries are
830 -- inlined by inlinenonrep), we will eventually have something like:
831 --
832 --   baz
833 --     @ CLasH.HardwareTypes.Bit
834 --     (D:Baz @ CLasH.HardwareTypes.Bit bitbaz)
835 --
836 -- Here, baz is the method selector for the baz method, while
837 -- D:Baz is the dictionary constructor for the Baz and bitbaz is the baz
838 -- method defined in the Baz Bit instance declaration.
839 --
840 -- To resolve this, we can look at the ClassOp IdInfo from the baz Id,
841 -- which contains the Class it is defined for. From the Class, we can
842 -- get a list of all selectors (both parent class selectors as well as
843 -- method selectors). Since the arguments to D:Baz (after the type
844 -- argument) correspond exactly to this list, we then look up baz in
845 -- that list and replace the entire expression by the corresponding 
846 -- argument to D:Baz.
847 --
848 -- We don't resolve methods that have a builtin translation (such as
849 -- ==), since the actual implementation is not always (easily)
850 -- translateable. For example, when deriving ==, GHC generates code
851 -- using $con2tag functions to translate a datacon to an int and compare
852 -- that with GHC.Prim.==# . Better to avoid that for now.
853 classopresolution :: Transform
854 classopresolution c expr@(App (App (Var sel) ty) dict) | not is_builtin =
855   case Id.isClassOpId_maybe sel of
856     -- Not a class op selector
857     Nothing -> return expr
858     Just cls -> case collectArgs dict of
859       (_, []) -> return expr -- Dict is not an application (e.g., not inlined yet)
860       (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)
861                                 | tyargs_neq ty ty' -> error $ "Normalize.classopresolution: Applying class selector to dictionary without matching type?\n" ++ pprString expr
862                                 | otherwise ->
863         let selector_ids = Class.classSelIds cls in
864         -- Find the selector used in the class' list of selectors
865         case List.elemIndex sel selector_ids of
866           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
867           -- Get the corresponding argument from the dictionary
868           Just n -> change (selectors!!n)
869       (_, _) -> return expr -- Not applying a variable? Don't touch
870   where
871     -- Compare two type arguments, returning True if they are _not_
872     -- equal
873     tyargs_neq (Type ty1) (Type ty2) = not $ Type.coreEqType ty1 ty2
874     tyargs_neq _ _ = True
875     -- Is this a builtin function / method?
876     is_builtin = elem (Name.getOccString sel) builtinIds
877
878 -- Leave all other expressions unchanged
879 classopresolution c expr = return expr
880
881 --------------------------------
882 -- Dictionary inlining
883 --------------------------------
884 -- Inline all top level dictionaries, that are in a position where
885 -- classopresolution can actually resolve them. This makes this
886 -- transformation look similar to classoperesolution below, but we'll
887 -- keep them separated for clarity. By not inlining other dictionaries,
888 -- we prevent expression sizes exploding when huge type level integer
889 -- dictionaries are inlined which can never be expanded (in casts, for
890 -- example).
891 inlinedict c expr@(App (App (Var sel) ty) (Var dict)) | not is_builtin && is_classop = do
892   body_maybe <- Trans.lift $ getGlobalBind dict
893   case body_maybe of
894     -- No body available (no source available, or a local variable /
895     -- argument)
896     Nothing -> return expr
897     Just body -> change (App (App (Var sel) ty) body)
898   where
899     -- Is this a builtin function / method?
900     is_builtin = elem (Name.getOccString sel) builtinIds
901     -- Are we dealing with a class operation selector?
902     is_classop = Maybe.isJust (Id.isClassOpId_maybe sel)
903
904 -- Leave all other expressions unchanged
905 inlinedict c expr = return expr
906
907
908 {-
909 --------------------------------
910 -- Identical let binding merging
911 --------------------------------
912 -- Merge two bindings in a let if they are identical 
913 -- TODO: We would very much like to use GHC's CSE module for this, but that
914 -- doesn't track if something changed or not, so we can't use it properly.
915 letmerge :: Transform
916 letmerge c expr@(Let _ _) = do
917   let (binds, res) = flattenLets expr
918   binds' <- domerge binds
919   return $ mkNonRecLets binds' res
920   where
921     domerge :: [(CoreBndr, CoreExpr)] -> TransformMonad [(CoreBndr, CoreExpr)]
922     domerge [] = return []
923     domerge (e:es) = do 
924       es' <- mapM (mergebinds e) es
925       es'' <- domerge es'
926       return (e:es'')
927
928     -- Uses the second bind to simplify the second bind, if applicable.
929     mergebinds :: (CoreBndr, CoreExpr) -> (CoreBndr, CoreExpr) -> TransformMonad (CoreBndr, CoreExpr)
930     mergebinds (b1, e1) (b2, e2)
931       -- Identical expressions? Replace the second binding with a reference to
932       -- the first binder.
933       | CoreUtils.cheapEqExpr e1 e2 = change $ (b2, Var b1)
934       -- Different expressions? Don't change
935       | otherwise = return (b2, e2)
936 -- Leave all other expressions unchanged
937 letmerge c expr = return expr
938 -}
939
940 --------------------------------
941 -- End of transformations
942 --------------------------------
943
944
945
946
947 -- What transforms to run?
948 transforms = [ ("inlinedict", inlinedict)
949              , ("inlinetoplevel", inlinetoplevel)
950              , ("inlinenonrepresult", inlinenonrepresult)
951              , ("knowncase", knowncase)
952              , ("classopresolution", classopresolution)
953              , ("argprop", argprop)
954              , ("funextract", funextract)
955              , ("eta", eta)
956              , ("beta", beta)
957              , ("appprop", appprop)
958              , ("castprop", castprop)
959              , ("letremovesimple", letremovesimple)
960              , ("letrec", letrec)
961              , ("letremove", letremove)
962              , ("retvalsimpl", retvalsimpl)
963              , ("letflat", letflat)
964              , ("scrutsimpl", scrutsimpl)
965              , ("scrutbndrremove", scrutbndrremove)
966              , ("casesimpl", casesimpl)
967              , ("caseremove", caseremove)
968              , ("inlinenonrep", inlinenonrep)
969              , ("appsimpl", appsimpl)
970              , ("letremoveunused", letremoveunused)
971              , ("castsimpl", castsimpl)
972              ]
973
974 -- | Returns the normalized version of the given function, or an error
975 -- if it is not a known global binder.
976 getNormalized ::
977   Bool -- ^ Allow the result to be unrepresentable?
978   -> CoreBndr -- ^ The function to get
979   -> TranslatorSession CoreExpr -- The normalized function body
980 getNormalized result_nonrep bndr = do
981   norm <- getNormalized_maybe result_nonrep bndr
982   return $ Maybe.fromMaybe
983     (error $ "Normalize.getNormalized: Unknown or non-representable function requested: " ++ show bndr)
984     norm
985
986 -- | Returns the normalized version of the given function, or Nothing
987 -- when the binder is not a known global binder or is not normalizeable.
988 getNormalized_maybe ::
989   Bool -- ^ Allow the result to be unrepresentable?
990   -> CoreBndr -- ^ The function to get
991   -> TranslatorSession (Maybe CoreExpr) -- The normalized function body
992
993 getNormalized_maybe result_nonrep bndr = do
994     expr_maybe <- getGlobalBind bndr
995     normalizeable <- isNormalizeable result_nonrep bndr
996     if not normalizeable || Maybe.isNothing expr_maybe
997       then
998         -- Binder not normalizeable or not found
999         return Nothing
1000       else do
1001         -- Binder found and is monomorphic. Normalize the expression
1002         -- and cache the result.
1003         normalized <- Utils.makeCached bndr tsNormalized $ 
1004           normalizeExpr (show bndr) (Maybe.fromJust expr_maybe)
1005         return (Just normalized)
1006
1007 -- | Normalize an expression
1008 normalizeExpr ::
1009   String -- ^ What are we normalizing? For debug output only.
1010   -> CoreSyn.CoreExpr -- ^ The expression to normalize 
1011   -> TranslatorSession CoreSyn.CoreExpr -- ^ The normalized expression
1012
1013 normalizeExpr what expr = do
1014       startcount <- MonadState.get tsTransformCounter 
1015       expr_uniqued <- genUniques expr
1016       -- Do a debug print, if requested
1017       let expr_uniqued' = Utils.traceIf (normalize_debug >= NormDbgFinal) (what ++ " before normalization:\n\n" ++ showSDoc ( ppr expr_uniqued ) ++ "\n") expr_uniqued
1018       -- Normalize this expression
1019       expr' <- dotransforms transforms expr_uniqued'
1020       endcount <- MonadState.get tsTransformCounter 
1021       -- Do a debug print, if requested
1022       Utils.traceIf (normalize_debug >= NormDbgFinal)  (what ++ " after normalization:\n\n" ++ showSDoc ( ppr expr') ++ "\nNeeded " ++ show (endcount - startcount) ++ " transformations to normalize " ++ what) $
1023         return expr'
1024
1025 -- | Split a normalized expression into the argument binders, top level
1026 --   bindings and the result binder. This function returns an error if
1027 --   the type of the expression is not representable.
1028 splitNormalized ::
1029   CoreExpr -- ^ The normalized expression
1030   -> ([CoreBndr], [Binding], CoreBndr)
1031 splitNormalized expr = 
1032   case splitNormalizedNonRep expr of
1033     (args, binds, Var res) -> (args, binds, res)
1034     _ -> error $ "Normalize.splitNormalized: Not in normal form: " ++ pprString expr ++ "\n"
1035
1036 -- Split a normalized expression, whose type can be unrepresentable.
1037 splitNormalizedNonRep::
1038   CoreExpr -- ^ The normalized expression
1039   -> ([CoreBndr], [Binding], CoreExpr)
1040 splitNormalizedNonRep expr = (args, binds, resexpr)
1041   where
1042     (args, letexpr) = CoreSyn.collectBinders expr
1043     (binds, resexpr) = flattenLets letexpr