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