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