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