1 {-# LANGUAGE PackageImports #-}
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
7 module Normalize (normalizeModule) where
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
21 import qualified UniqSupply
22 import qualified CoreUtils
26 import qualified VarSet
27 import qualified CoreFVs
28 import qualified CoreUtils
29 import qualified MkCore
30 import Outputable ( showSDoc, ppr, nest )
38 --------------------------------
39 -- Start of transformations
40 --------------------------------
42 --------------------------------
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
52 etatop = notappargs ("eta", eta)
54 --------------------------------
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'
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)
72 --------------------------------
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')
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)
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)
96 --------------------------------
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)
113 --------------------------------
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
126 return $ Let (Rec binds') expr
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)
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 -> return True; otherwise -> return False))
145 --------------------------------
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
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 inlinenonreptop :: Transform
161 inlinenonreptop = everywhere ("inlinenonrep", inlinebind ((Monad.liftM not) . isRepr . snd))
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
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)
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
196 -- Generate a single wild binder, since they are all the same
198 -- Wilden the binders of one alt, producing a list of bindings as a
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
207 let newalt = (con, wildbndrs, expr)
208 return (bindings, newalt)
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))
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
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)
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
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
247 if null bindings then return expr else change newlet
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)
272 --------------------------------
274 --------------------------------
275 -- Remove case statements that have only a single alternative and only wild
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)
287 --------------------------------
288 -- Argument extraction
289 --------------------------------
290 -- Make sure that all arguments of a representable type are simple variables.
291 appsimpl, appsimpltop :: Transform
292 -- Don't simplify arguments that are already simple.
293 appsimpl expr@(App f (Var v)) = return expr
294 -- Simplify all representable arguments. Do this by introducing a new Let
295 -- that binds the argument and passing the new binder in the application.
296 appsimpl expr@(App f arg) = do
297 -- Check runtime representability
300 then do -- Extract representable arguments
301 id <- mkInternalVar "arg" (CoreUtils.exprType arg)
302 change $ Let (Rec [(id, arg)]) (App f (Var id))
303 else -- Leave non-representable arguments unchanged
305 -- Leave all other expressions unchanged
306 appsimpl expr = return expr
307 -- Perform this transform everywhere
308 appsimpltop = everywhere ("appsimpl", appsimpl)
310 --------------------------------
311 -- Function-typed argument propagation
312 --------------------------------
313 -- Remove all applications to function-typed arguments, by duplication the
314 -- function called with the function-typed parameter replaced by the free
315 -- variables of the argument passed in.
316 argprop, argproptop :: Transform
317 -- Transform any application of a named function (i.e., skip applications of
318 -- lambda's). Also skip applications that have arguments with free type
319 -- variables, since we can't inline those.
320 argprop expr@(App _ _) | is_var fexpr = do
321 -- Find the body of the function called
322 body_maybe <- Trans.lift $ getGlobalBind f
325 -- Process each of the arguments in turn
326 (args', changed) <- Writer.listen $ mapM doarg args
327 -- See if any of the arguments changed
328 case Monoid.getAny changed of
330 let (newargs', newparams', oldargs) = unzip3 args'
331 let newargs = concat newargs'
332 let newparams = concat newparams'
333 -- Create a new body that consists of a lambda for all new arguments and
334 -- the old body applied to some arguments.
335 let newbody = MkCore.mkCoreLams newparams (MkCore.mkCoreApps body oldargs)
336 -- Create a new function with the same name but a new body
337 newf <- mkFunction f newbody
338 -- Replace the original application with one of the new function to the
340 change $ MkCore.mkCoreApps (Var newf) newargs
342 -- Don't change the expression if none of the arguments changed
345 -- If we don't have a body for the function called, leave it unchanged (it
346 -- should be a primitive function then).
347 Nothing -> return expr
349 -- Find the function called and the arguments
350 (fexpr, args) = collectArgs expr
353 -- Process a single argument and return (args, bndrs, arg), where args are
354 -- the arguments to replace the given argument in the original
355 -- application, bndrs are the binders to include in the top-level lambda
356 -- in the new function body, and arg is the argument to apply to the old
358 doarg :: CoreExpr -> TransformMonad ([CoreExpr], [CoreBndr], CoreExpr)
361 bndrs <- Trans.lift getGlobalBinders
362 let interesting var = Var.isLocalVar var && (not $ var `elem` bndrs)
363 if not repr && not (is_var arg && interesting (exprToVar arg)) && not (has_free_tyvars arg)
365 -- Propagate all complex arguments that are not representable, but not
366 -- arguments with free type variables (since those would require types
367 -- not known yet, which will always be known eventually).
368 -- Find interesting free variables, each of which should be passed to
369 -- the new function instead of the original function argument.
371 -- Interesting vars are those that are local, but not available from the
372 -- top level scope (functions from this module are defined as local, but
373 -- they're not local to this function, so we can freely move references
374 -- to them into another function).
375 let free_vars = VarSet.varSetElems $ CoreFVs.exprSomeFreeVars interesting arg
376 -- Mark the current expression as changed
378 return (map Var free_vars, free_vars, arg)
380 -- Representable types will not be propagated, and arguments with free
381 -- type variables will be propagated later.
382 -- TODO: preserve original naming?
383 id <- mkBinderFor arg "param"
384 -- Just pass the original argument to the new function, which binds it
385 -- to a new id and just pass that new id to the old function body.
386 return ([arg], [id], mkReferenceTo id)
387 -- Leave all other expressions unchanged
388 argprop expr = return expr
389 -- Perform this transform everywhere
390 argproptop = everywhere ("argprop", argprop)
392 --------------------------------
393 -- Function-typed argument extraction
394 --------------------------------
395 -- This transform takes any function-typed argument that cannot be propagated
396 -- (because the function that is applied to it is a builtin function), and
397 -- puts it in a brand new top level binder. This allows us to for example
398 -- apply map to a lambda expression This will not conflict with inlinefun,
399 -- since that only inlines local let bindings, not top level bindings.
400 funextract, funextracttop :: Transform
401 funextract expr@(App _ _) | is_var fexpr = do
402 body_maybe <- Trans.lift $ getGlobalBind f
404 -- We don't have a function body for f, so we can perform this transform.
406 -- Find the new arguments
407 args' <- mapM doarg args
408 -- And update the arguments. We use return instead of changed, so the
409 -- changed flag doesn't get set if none of the args got changed.
410 return $ MkCore.mkCoreApps fexpr args'
411 -- We have a function body for f, leave this application to funprop
412 Just _ -> return expr
414 -- Find the function called and the arguments
415 (fexpr, args) = collectArgs expr
417 -- Change any arguments that have a function type, but are not simple yet
418 -- (ie, a variable or application). This means to create a new function
419 -- for map (\f -> ...) b, but not for map (foo a) b.
421 -- We could use is_applicable here instead of is_fun, but I think
422 -- arguments to functions could only have forall typing when existential
423 -- typing is enabled. Not sure, though.
424 doarg arg | not (is_simple arg) && is_fun arg = do
425 -- Create a new top level binding that binds the argument. Its body will
426 -- be extended with lambda expressions, to take any free variables used
427 -- by the argument expression.
428 let free_vars = VarSet.varSetElems $ CoreFVs.exprFreeVars arg
429 let body = MkCore.mkCoreLams free_vars arg
430 id <- mkBinderFor body "fun"
431 Trans.lift $ addGlobalBind id body
432 -- Replace the argument with a reference to the new function, applied to
434 change $ MkCore.mkCoreApps (Var id) (map Var free_vars)
435 -- Leave all other arguments untouched
436 doarg arg = return arg
438 -- Leave all other expressions unchanged
439 funextract expr = return expr
440 -- Perform this transform everywhere
441 funextracttop = everywhere ("funextract", funextract)
443 --------------------------------
444 -- End of transformations
445 --------------------------------
450 -- What transforms to run?
451 transforms = [argproptop, funextracttop, etatop, betatop, castproptop, letremovetop, letrectop, letsimpltop, letflattop, casewildtop, scrutsimpltop, casevalsimpltop, caseremovetop, inlinenonreptop, appsimpltop]
453 -- Turns the given bind into VHDL
455 UniqSupply.UniqSupply -- ^ A UniqSupply we can use
456 -> [(CoreBndr, CoreExpr)] -- ^ All bindings we know (i.e., in the current module)
457 -> [CoreBndr] -- ^ The bindings to generate VHDL for (i.e., the top level bindings)
458 -> [Bool] -- ^ For each of the bindings to generate VHDL for, if it is stateful
459 -> [(CoreBndr, CoreExpr)] -- ^ The resulting VHDL
461 normalizeModule uniqsupply bindings generate_for statefuls = runTransformSession uniqsupply $ do
462 -- Put all the bindings in this module in the tsBindings map
463 putA tsBindings (Map.fromList bindings)
464 -- (Recursively) normalize each of the requested bindings
465 mapM normalizeBind generate_for
466 -- Get all initial bindings and the ones we produced
467 bindings_map <- getA tsBindings
468 let bindings = Map.assocs bindings_map
469 normalized_bindings <- getA tsNormalized
470 -- But return only the normalized bindings
471 return $ filter ((flip VarSet.elemVarSet normalized_bindings) . fst) bindings
473 normalizeBind :: CoreBndr -> TransformSession ()
475 -- Don't normalize global variables, these should be either builtin
476 -- functions or data constructors.
477 Monad.when (Var.isLocalIdVar bndr) $ do
478 -- Skip binders that have a polymorphic type, since it's impossible to
479 -- create polymorphic hardware.
480 if is_poly (Var bndr)
482 -- This should really only happen at the top level... TODO: Give
483 -- a different error if this happens down in the recursion.
484 error $ "\nNormalize.normalizeBind: Function " ++ show bndr ++ " is polymorphic, can't normalize"
486 normalized_funcs <- getA tsNormalized
487 -- See if this function was normalized already
488 if VarSet.elemVarSet bndr normalized_funcs
490 -- Yup, don't do it again
493 -- Nope, note that it has been and do it.
494 modA tsNormalized (flip VarSet.extendVarSet bndr)
495 expr_maybe <- getGlobalBind bndr
498 -- Introduce an empty Let at the top level, so there will always be
499 -- a let in the expression (none of the transformations will remove
501 let expr' = Let (Rec []) expr
502 -- Normalize this expression
503 trace ("Transforming " ++ (show bndr) ++ "\nBefore:\n\n" ++ showSDoc ( ppr expr' ) ++ "\n") $ return ()
504 expr' <- dotransforms transforms expr'
505 trace ("\nAfter:\n\n" ++ showSDoc ( ppr expr')) $ return ()
506 -- And store the normalized version in the session
507 modA tsBindings (Map.insert bndr expr')
508 -- Find all vars used with a function type. All of these should be global
509 -- binders (i.e., functions used), since any local binders with a function
510 -- type should have been inlined already.
511 let used_funcs_set = CoreFVs.exprSomeFreeVars (\v -> (Type.isFunTy . snd . Type.splitForAllTys . Id.idType) v) expr'
512 let used_funcs = VarSet.varSetElems used_funcs_set
513 -- Process each of the used functions recursively
514 mapM normalizeBind used_funcs
516 -- We don't have a value for this binder. This really shouldn't
517 -- happen for local id's...
518 Nothing -> error $ "\nNormalize.normalizeBind: No value found for binder " ++ pprString bndr ++ "? This should not happen!"