Merge git://github.com/darchon/clash into cλash
[matthijs/master-project/cλash.git] / 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 Normalize (normalizeModule) where
8
9 -- Standard modules
10 import Debug.Trace
11 import qualified Maybe
12 import qualified "transformers" Control.Monad.Trans as Trans
13 import qualified Control.Monad as Monad
14 import qualified Control.Monad.Trans.Writer as Writer
15 import qualified Data.Map as Map
16 import qualified Data.Monoid as Monoid
17 import Data.Accessor
18
19 -- GHC API
20 import CoreSyn
21 import qualified UniqSupply
22 import qualified CoreUtils
23 import qualified Type
24 import qualified Id
25 import qualified Var
26 import qualified VarSet
27 import qualified CoreFVs
28 import qualified CoreUtils
29 import qualified MkCore
30 import Outputable ( showSDoc, ppr, nest )
31
32 -- Local imports
33 import NormalizeTypes
34 import NormalizeTools
35 import CoreTools
36 import Pretty
37
38 --------------------------------
39 -- Start of transformations
40 --------------------------------
41
42 --------------------------------
43 -- η abstraction
44 --------------------------------
45 eta, etatop :: Transform
46 eta expr | is_fun expr && not (is_lam expr) = do
47   let arg_ty = (fst . Type.splitFunTy . CoreUtils.exprType) expr
48   id <- mkInternalVar "param" arg_ty
49   change (Lam id (App expr (Var id)))
50 -- Leave all other expressions unchanged
51 eta e = return e
52 etatop = notappargs ("eta", eta)
53
54 --------------------------------
55 -- β-reduction
56 --------------------------------
57 beta, betatop :: Transform
58 -- Substitute arg for x in expr
59 beta (App (Lam x expr) arg) = change $ substitute [(x, arg)] expr
60 -- Propagate the application into the let
61 beta (App (Let binds expr) arg) = change $ Let binds (App expr arg)
62 -- Propagate the application into each of the alternatives
63 beta (App (Case scrut b ty alts) arg) = change $ Case scrut b ty' alts'
64   where 
65     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (App expr arg))) alts
66     ty' = CoreUtils.applyTypeToArg ty arg
67 -- Leave all other expressions unchanged
68 beta expr = return expr
69 -- Perform this transform everywhere
70 betatop = everywhere ("beta", beta)
71
72 --------------------------------
73 -- Cast propagation
74 --------------------------------
75 -- Try to move casts as much downward as possible.
76 castprop, castproptop :: Transform
77 castprop (Cast (Let binds expr) ty) = change $ Let binds (Cast expr ty)
78 castprop expr@(Cast (Case scrut b _ alts) ty) = change (Case scrut b ty alts')
79   where
80     alts' = map (\(con, bndrs, expr) -> (con, bndrs, (Cast expr ty))) alts
81 -- Leave all other expressions unchanged
82 castprop expr = return expr
83 -- Perform this transform everywhere
84 castproptop = everywhere ("castprop", castprop)
85
86 --------------------------------
87 -- let recursification
88 --------------------------------
89 letrec, letrectop :: Transform
90 letrec (Let (NonRec b expr) res) = change $ Let (Rec [(b, expr)]) res
91 -- Leave all other expressions unchanged
92 letrec expr = return expr
93 -- Perform this transform everywhere
94 letrectop = everywhere ("letrec", letrec)
95
96 --------------------------------
97 -- let simplification
98 --------------------------------
99 letsimpl, letsimpltop :: Transform
100 -- Don't simplifiy lets that are already simple
101 letsimpl expr@(Let _ (Var _)) = return expr
102 -- Put the "in ..." value of a let in its own binding, but not when the
103 -- expression is applicable (to prevent loops with inlinefun).
104 letsimpl (Let (Rec binds) expr) | not $ is_applicable expr = do
105   id <- mkInternalVar "foo" (CoreUtils.exprType expr)
106   let bind = (id, expr)
107   change $ Let (Rec (bind:binds)) (Var id)
108 -- Leave all other expressions unchanged
109 letsimpl expr = return expr
110 -- Perform this transform everywhere
111 letsimpltop = everywhere ("letsimpl", letsimpl)
112
113 --------------------------------
114 -- let flattening
115 --------------------------------
116 letflat, letflattop :: Transform
117 letflat (Let (Rec binds) expr) = do
118   -- Turn each binding into a list of bindings (possibly containing just one
119   -- element, of course)
120   bindss <- Monad.mapM flatbind binds
121   -- Concat all the bindings
122   let binds' = concat bindss
123   -- Return the new let. We don't use change here, since possibly nothing has
124   -- changed. If anything has changed, flatbind has already flagged that
125   -- change.
126   return $ Let (Rec binds') expr
127   where
128     -- Turns a binding of a let into a multiple bindings, or any other binding
129     -- into a list with just that binding
130     flatbind :: (CoreBndr, CoreExpr) -> TransformMonad [(CoreBndr, CoreExpr)]
131     flatbind (b, Let (Rec binds) expr) = change ((b, expr):binds)
132     flatbind (b, expr) = return [(b, expr)]
133 -- Leave all other expressions unchanged
134 letflat expr = return expr
135 -- Perform this transform everywhere
136 letflattop = everywhere ("letflat", letflat)
137
138 --------------------------------
139 -- Simple let binding removal
140 --------------------------------
141 -- Remove a = b bindings from let expressions everywhere
142 letremovetop :: Transform
143 letremovetop = everywhere ("letremove", inlinebind (\(b, e) -> case e of (Var v) | not $ Id.isDataConWorkId v -> True; otherwise -> False))
144
145 --------------------------------
146 -- Function inlining
147 --------------------------------
148 -- Remove a = B bindings, with B :: a -> b, or B :: forall x . T, from let
149 -- expressions everywhere. This means that any value that still needs to be
150 -- applied to something else (polymorphic values need to be applied to a
151 -- Type) will be inlined, and will eventually be applied to all their
152 -- arguments.
153 --
154 -- This is a tricky function, which is prone to create loops in the
155 -- transformations. To fix this, we make sure that no transformation will
156 -- create a new let binding with a function type. These other transformations
157 -- will just not work on those function-typed values at first, but the other
158 -- transformations (in particular β-reduction) should make sure that the type
159 -- of those values eventually becomes primitive.
160 inlinefuntop :: Transform
161 inlinefuntop = everywhere ("inlinefun", inlinebind (is_applicable . snd))
162
163 --------------------------------
164 -- Scrutinee simplification
165 --------------------------------
166 scrutsimpl,scrutsimpltop :: Transform
167 -- Don't touch scrutinees that are already simple
168 scrutsimpl expr@(Case (Var _) _ _ _) = return expr
169 -- Replace all other cases with a let that binds the scrutinee and a new
170 -- simple scrutinee, but not when the scrutinee is applicable (to prevent
171 -- loops with inlinefun, though I don't think a scrutinee can be
172 -- applicable...)
173 scrutsimpl (Case scrut b ty alts) | not $ is_applicable scrut = do
174   id <- mkInternalVar "scrut" (CoreUtils.exprType scrut)
175   change $ Let (Rec [(id, scrut)]) (Case (Var id) b ty alts)
176 -- Leave all other expressions unchanged
177 scrutsimpl expr = return expr
178 -- Perform this transform everywhere
179 scrutsimpltop = everywhere ("scrutsimpl", scrutsimpl)
180
181 --------------------------------
182 -- Case binder wildening
183 --------------------------------
184 casewild, casewildtop :: Transform
185 casewild expr@(Case scrut b ty alts) = do
186   (bindingss, alts') <- (Monad.liftM unzip) $ mapM doalt alts
187   let bindings = concat bindingss
188   -- Replace the case with a let with bindings and a case
189   let newlet = (Let (Rec bindings) (Case scrut b ty alts'))
190   -- If there are no non-wild binders, or this case is already a simple
191   -- selector (i.e., a single alt with exactly one binding), already a simple
192   -- selector altan no bindings (i.e., no wild binders in the original case),
193   -- don't change anything, otherwise, replace the case.
194   if null bindings || length alts == 1 && length bindings == 1 then return expr else change newlet 
195   where
196   -- Generate a single wild binder, since they are all the same
197   wild = Id.mkWildId
198   -- Wilden the binders of one alt, producing a list of bindings as a
199   -- sideeffect.
200   doalt :: CoreAlt -> TransformMonad ([(CoreBndr, CoreExpr)], CoreAlt)
201   doalt (con, bndrs, expr) = do
202     bindings_maybe <- Monad.zipWithM mkextracts bndrs [0..]
203     let bindings = Maybe.catMaybes bindings_maybe
204     -- We replace the binders with wild binders only. We can leave expr
205     -- unchanged, since the new bindings bind the same vars as the original
206     -- did.
207     let newalt = (con, wildbndrs, expr)
208     return (bindings, newalt)
209     where
210       -- Make all binders wild
211       wildbndrs = map (\bndr -> Id.mkWildId (Id.idType bndr)) bndrs
212       -- Creates a case statement to retrieve the ith element from the scrutinee
213       -- and binds that to b.
214       mkextracts :: CoreBndr -> Int -> TransformMonad (Maybe (CoreBndr, CoreExpr))
215       mkextracts b i =
216         -- TODO: Use free variables instead of is_wild. is_wild is a hack.
217         if is_wild b || Type.isFunTy (Id.idType b) 
218           -- Don't create extra bindings for binders that are already wild, or
219           -- for binders that bind function types (to prevent loops with
220           -- inlinefun).
221           then return Nothing
222           else do
223             -- Create on new binder that will actually capture a value in this
224             -- case statement, and return it
225             let bty = (Id.idType b)
226             id <- mkInternalVar "sel" bty
227             let binders = take i wildbndrs ++ [id] ++ drop (i+1) wildbndrs
228             return $ Just (b, Case scrut b bty [(con, binders, Var id)])
229 -- Leave all other expressions unchanged
230 casewild expr = return expr
231 -- Perform this transform everywhere
232 casewildtop = everywhere ("casewild", casewild)
233
234 --------------------------------
235 -- Case value simplification
236 --------------------------------
237 casevalsimpl, casevalsimpltop :: Transform
238 casevalsimpl expr@(Case scrut b ty alts) = do
239   -- Try to simplify each alternative, resulting in an optional binding and a
240   -- new alternative.
241   (bindings_maybe, alts') <- (Monad.liftM unzip) $ mapM doalt alts
242   let bindings = Maybe.catMaybes bindings_maybe
243   -- Create a new let around the case, that binds of the cases values.
244   let newlet = Let (Rec bindings) (Case scrut b ty alts')
245   -- If there were no values that needed and allowed simplification, don't
246   -- change the case.
247   if null bindings then return expr else change newlet 
248   where
249     doalt :: CoreAlt -> TransformMonad (Maybe (CoreBndr, CoreExpr), CoreAlt)
250     -- Don't simplify values that are already simple
251     doalt alt@(con, bndrs, Var _) = return (Nothing, alt)
252     -- Simplify each alt by creating a new id, binding the case value to it and
253     -- replacing the case value with that id. Only do this when the case value
254     -- does not use any of the binders bound by this alternative, for that would
255     -- cause those binders to become unbound when moving the value outside of
256     -- the case statement. Also, don't create a binding for applicable
257     -- expressions, to prevent loops with inlinefun.
258     doalt (con, bndrs, expr) | (not usesvars) && (not $ is_applicable expr) = do
259       id <- mkInternalVar "caseval" (CoreUtils.exprType expr)
260       -- We don't flag a change here, since casevalsimpl will do that above
261       -- based on Just we return here.
262       return $ (Just (id, expr), (con, bndrs, Var id))
263       -- Find if any of the binders are used by expr
264       where usesvars = (not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` bndrs))) expr
265     -- Don't simplify anything else
266     doalt alt = return (Nothing, alt)
267 -- Leave all other expressions unchanged
268 casevalsimpl expr = return expr
269 -- Perform this transform everywhere
270 casevalsimpltop = everywhere ("casevalsimpl", casevalsimpl)
271
272 --------------------------------
273 -- Case removal
274 --------------------------------
275 -- Remove case statements that have only a single alternative and only wild
276 -- binders.
277 caseremove, caseremovetop :: Transform
278 -- Replace a useless case by the value of its single alternative
279 caseremove (Case scrut b ty [(con, bndrs, expr)]) | not usesvars = change expr
280     -- Find if any of the binders are used by expr
281     where usesvars = (not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` bndrs))) expr
282 -- Leave all other expressions unchanged
283 caseremove expr = return expr
284 -- Perform this transform everywhere
285 caseremovetop = everywhere ("caseremove", caseremove)
286
287 --------------------------------
288 -- Application simplification
289 --------------------------------
290 -- Make sure that all arguments in an application are simple variables.
291 appsimpl, appsimpltop :: Transform
292 -- Don't simplify arguments that are already simple. Do simplify datacons,
293 -- however, since we can't portmap literals.
294 appsimpl expr@(App f (Var v)) | not $ Id.isDataConWorkId v = return expr
295 -- Simplify all non-applicable (to prevent loops with inlinefun) arguments,
296 -- except for type arguments (since a let can't bind type vars, only a lambda
297 -- can). Do this by introducing a new Let that binds the argument and passing
298 -- the new binder in the application.
299 appsimpl (App f expr) | (not $ is_applicable expr) && (not $ CoreSyn.isTypeArg expr) = do
300   id <- mkInternalVar "arg" (CoreUtils.exprType expr)
301   change $ Let (Rec [(id, expr)]) (App f (Var id))
302 -- Leave all other expressions unchanged
303 appsimpl expr = return expr
304 -- Perform this transform everywhere
305 appsimpltop = everywhere ("appsimpl", appsimpl)
306
307
308 --------------------------------
309 -- Type argument propagation
310 --------------------------------
311 -- Remove all applications to type arguments, by duplicating the function
312 -- called with the type application in its new definition. We leave
313 -- dictionaries that might be associated with the type untouched, the funprop
314 -- transform should propagate these later on.
315 typeprop, typeproptop :: Transform
316 -- Transform any function that is applied to a type argument. Since type
317 -- arguments are always the first ones to apply and we'll remove all type
318 -- arguments, we can simply do them one by one. We only propagate type
319 -- arguments without any free tyvars, since tyvars those wouldn't be in scope
320 -- in the new function.
321 typeprop expr@(App (Var f) arg@(Type ty)) | not $ has_free_tyvars arg = do
322   body_maybe <- Trans.lift $ getGlobalBind f
323   case body_maybe of
324     Just body -> do
325       let newbody = App body (Type ty)
326       -- Create a new function with the same name but a new body
327       newf <- mkFunction f newbody
328       -- Replace the application with this new function
329       change (Var newf)
330     -- If we don't have a body for the function called, leave it unchanged (it
331     -- should be a primitive function then).
332     Nothing -> return expr
333 -- Leave all other expressions unchanged
334 typeprop expr = return expr
335 -- Perform this transform everywhere
336 typeproptop = everywhere ("typeprop", typeprop)
337
338
339 --------------------------------
340 -- Function-typed argument propagation
341 --------------------------------
342 -- Remove all applications to function-typed arguments, by duplication the
343 -- function called with the function-typed parameter replaced by the free
344 -- variables of the argument passed in.
345 funprop, funproptop :: Transform
346 -- Transform any application of a named function (i.e., skip applications of
347 -- lambda's). Also skip applications that have arguments with free type
348 -- variables, since we can't inline those.
349 funprop expr@(App _ _) | is_var fexpr && not (any has_free_tyvars args) = do
350   -- Find the body of the function called
351   body_maybe <- Trans.lift $ getGlobalBind f
352   case body_maybe of
353     Just body -> do
354       -- Process each of the arguments in turn
355       (args', changed) <- Writer.listen $ mapM doarg args
356       -- See if any of the arguments changed
357       case Monoid.getAny changed of
358         True -> do
359           let (newargs', newparams', oldargs) = unzip3 args'
360           let newargs = concat newargs'
361           let newparams = concat newparams'
362           -- Create a new body that consists of a lambda for all new arguments and
363           -- the old body applied to some arguments.
364           let newbody = MkCore.mkCoreLams newparams (MkCore.mkCoreApps body oldargs)
365           -- Create a new function with the same name but a new body
366           newf <- mkFunction f newbody
367           -- Replace the original application with one of the new function to the
368           -- new arguments.
369           change $ MkCore.mkCoreApps (Var newf) newargs
370         False ->
371           -- Don't change the expression if none of the arguments changed
372           return expr
373       
374     -- If we don't have a body for the function called, leave it unchanged (it
375     -- should be a primitive function then).
376     Nothing -> return expr
377   where
378     -- Find the function called and the arguments
379     (fexpr, args) = collectArgs expr
380     Var f = fexpr
381
382     -- Process a single argument and return (args, bndrs, arg), where args are
383     -- the arguments to replace the given argument in the original
384     -- application, bndrs are the binders to include in the top-level lambda
385     -- in the new function body, and arg is the argument to apply to the old
386     -- function body.
387     doarg :: CoreExpr -> TransformMonad ([CoreExpr], [CoreBndr], CoreExpr)
388     doarg arg | is_fun arg = do
389       bndrs <- Trans.lift getGlobalBinders
390       -- Find interesting free variables, each of which should be passed to
391       -- the new function instead of the original function argument.
392       -- 
393       -- Interesting vars are those that are local, but not available from the
394       -- top level scope (functions from this module are defined as local, but
395       -- they're not local to this function, so we can freely move references
396       -- to them into another function).
397       let interesting var = Var.isLocalVar var && (not $ var `elem` bndrs)
398       let free_vars = VarSet.varSetElems $ CoreFVs.exprSomeFreeVars interesting arg
399       -- Mark the current expression as changed
400       setChanged
401       return (map Var free_vars, free_vars, arg)
402     -- Non-functiontyped arguments can be unchanged. Note that this handles
403     -- both values and types.
404     doarg arg = do
405       -- TODO: preserve original naming?
406       id <- mkBinderFor arg "param"
407       -- Just pass the original argument to the new function, which binds it
408       -- to a new id and just pass that new id to the old function body.
409       return ([arg], [id], mkReferenceTo id) 
410 -- Leave all other expressions unchanged
411 funprop expr = return expr
412 -- Perform this transform everywhere
413 funproptop = everywhere ("funprop", funprop)
414
415 --------------------------------
416 -- Function-typed argument extraction
417 --------------------------------
418 -- This transform takes any function-typed argument that cannot be propagated
419 -- (because the function that is applied to it is a builtin function), and
420 -- puts it in a brand new top level binder. This allows us to for example
421 -- apply map to a lambda expression This will not conflict with inlinefun,
422 -- since that only inlines local let bindings, not top level bindings.
423 funextract, funextracttop :: Transform
424 funextract expr@(App _ _) | is_var fexpr = do
425   body_maybe <- Trans.lift $ getGlobalBind f
426   case body_maybe of
427     -- We don't have a function body for f, so we can perform this transform.
428     Nothing -> do
429       -- Find the new arguments
430       args' <- mapM doarg args
431       -- And update the arguments. We use return instead of changed, so the
432       -- changed flag doesn't get set if none of the args got changed.
433       return $ MkCore.mkCoreApps fexpr args'
434     -- We have a function body for f, leave this application to funprop
435     Just _ -> return expr
436   where
437     -- Find the function called and the arguments
438     (fexpr, args) = collectArgs expr
439     Var f = fexpr
440     -- Change any arguments that have a function type, but are not simple yet
441     -- (ie, a variable or application). This means to create a new function
442     -- for map (\f -> ...) b, but not for map (foo a) b.
443     --
444     -- We could use is_applicable here instead of is_fun, but I think
445     -- arguments to functions could only have forall typing when existential
446     -- typing is enabled. Not sure, though.
447     doarg arg | not (is_simple arg) && is_fun arg = do
448       -- Create a new top level binding that binds the argument. Its body will
449       -- be extended with lambda expressions, to take any free variables used
450       -- by the argument expression.
451       let free_vars = VarSet.varSetElems $ CoreFVs.exprFreeVars arg
452       let body = MkCore.mkCoreLams free_vars arg
453       id <- mkBinderFor body "fun"
454       Trans.lift $ addGlobalBind id body
455       -- Replace the argument with a reference to the new function, applied to
456       -- all vars it uses.
457       change $ MkCore.mkCoreApps (Var id) (map Var free_vars)
458     -- Leave all other arguments untouched
459     doarg arg = return arg
460
461 -- Leave all other expressions unchanged
462 funextract expr = return expr
463 -- Perform this transform everywhere
464 funextracttop = everywhere ("funextract", funextract)
465
466 --------------------------------
467 -- End of transformations
468 --------------------------------
469
470
471
472
473 -- What transforms to run?
474 transforms = [typeproptop, funproptop, funextracttop, etatop, betatop, castproptop, letremovetop, letrectop, letsimpltop, letflattop, casewildtop, scrutsimpltop, casevalsimpltop, caseremovetop, inlinefuntop, appsimpltop]
475
476 -- Turns the given bind into VHDL
477 normalizeModule :: 
478   UniqSupply.UniqSupply -- ^ A UniqSupply we can use
479   -> [(CoreBndr, CoreExpr)]  -- ^ All bindings we know (i.e., in the current module)
480   -> [CoreBndr]  -- ^ The bindings to generate VHDL for (i.e., the top level bindings)
481   -> [Bool] -- ^ For each of the bindings to generate VHDL for, if it is stateful
482   -> [(CoreBndr, CoreExpr)] -- ^ The resulting VHDL
483
484 normalizeModule uniqsupply bindings generate_for statefuls = runTransformSession uniqsupply $ do
485   -- Put all the bindings in this module in the tsBindings map
486   putA tsBindings (Map.fromList bindings)
487   -- (Recursively) normalize each of the requested bindings
488   mapM normalizeBind generate_for
489   -- Get all initial bindings and the ones we produced
490   bindings_map <- getA tsBindings
491   let bindings = Map.assocs bindings_map
492   normalized_bindings <- getA tsNormalized
493   -- But return only the normalized bindings
494   return $ filter ((flip VarSet.elemVarSet normalized_bindings) . fst) bindings
495
496 normalizeBind :: CoreBndr -> TransformSession ()
497 normalizeBind bndr =
498   -- Don't normalize global variables, these should be either builtin
499   -- functions or data constructors.
500   Monad.when (Var.isLocalIdVar bndr) $ do
501     -- Skip binders that have a polymorphic type, since it's impossible to
502     -- create polymorphic hardware.
503     if is_poly (Var bndr)
504       then
505         -- This should really only happen at the top level... TODO: Give
506         -- a different error if this happens down in the recursion.
507         error $ "\nNormalize.normalizeBind: Function " ++ show bndr ++ " is polymorphic, can't normalize"
508       else do
509         normalized_funcs <- getA tsNormalized
510         -- See if this function was normalized already
511         if VarSet.elemVarSet bndr normalized_funcs
512           then
513             -- Yup, don't do it again
514             return ()
515           else do
516             -- Nope, note that it has been and do it.
517             modA tsNormalized (flip VarSet.extendVarSet bndr)
518             expr_maybe <- getGlobalBind bndr
519             case expr_maybe of 
520               Just expr -> do
521                 -- Introduce an empty Let at the top level, so there will always be
522                 -- a let in the expression (none of the transformations will remove
523                 -- the last let).
524                 let expr' = Let (Rec []) expr
525                 -- Normalize this expression
526                 trace ("Transforming " ++ (show bndr) ++ "\nBefore:\n\n" ++ showSDoc ( ppr expr' ) ++ "\n") $ return ()
527                 expr' <- dotransforms transforms expr'
528                 trace ("\nAfter:\n\n" ++ showSDoc ( ppr expr')) $ return ()
529                 -- And store the normalized version in the session
530                 modA tsBindings (Map.insert bndr expr')
531                 -- Find all vars used with a function type. All of these should be global
532                 -- binders (i.e., functions used), since any local binders with a function
533                 -- type should have been inlined already.
534                 let used_funcs_set = CoreFVs.exprSomeFreeVars (\v -> (Type.isFunTy . snd . Type.splitForAllTys . Id.idType) v) expr'
535                 let used_funcs = VarSet.varSetElems used_funcs_set
536                 -- Process each of the used functions recursively
537                 mapM normalizeBind used_funcs
538                 return ()
539               -- We don't have a value for this binder. This really shouldn't
540               -- happen for local id's...
541               Nothing -> error $ "\nNormalize.normalizeBind: No value found for binder " ++ pprString bndr ++ "? This should not happen!"