X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=c%CE%BBash%2FCLasH%2FNormalize.hs;h=d6acc13b19dbc82e37ffaa08195421c63e1f4e52;hb=118a85a1ad01d78cf9e4a2e63d0f7b4f35bb8a1f;hp=cf33b7bb3d9aab751eb071db017975c35e7bb04d;hpb=9a75989431be8c2188283c9dff0c105dabb84420;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git "a/c\316\273ash/CLasH/Normalize.hs" "b/c\316\273ash/CLasH/Normalize.hs" index cf33b7b..d6acc13 100644 --- "a/c\316\273ash/CLasH/Normalize.hs" +++ "b/c\316\273ash/CLasH/Normalize.hs" @@ -20,10 +20,13 @@ import qualified Data.Map as Map -- GHC API import CoreSyn import qualified CoreUtils +import qualified BasicTypes import qualified Type +import qualified TysWiredIn import qualified Id import qualified Var import qualified Name +import qualified DataCon import qualified VarSet import qualified CoreFVs import qualified Class @@ -45,17 +48,16 @@ import CLasH.Utils.Pretty -------------------------------- -------------------------------- --- η abstraction +-- η expansion -------------------------------- +-- Make sure all parameters to the normalized functions are named by top +-- level lambda expressions. For this we apply η expansion to the +-- function body (possibly enclosed in some lambda abstractions) while +-- it has a function type. Eventually this will result in a function +-- body consisting of a bunch of nested lambdas containing a +-- non-function value (e.g., a complete application). eta, etatop :: Transform --- Don't apply to expressions that are applied, since that would cause --- us to apply to our own result indefinitely. -eta (AppFirst:_) expr = return expr --- Also don't apply to arguments, since this can cause loops with --- funextract. This isn't the proper solution, but due to an --- implementation bug in notappargs, this is how it used to work so far. -eta (AppSecond:_) expr = return expr -eta c expr | is_fun expr && not (is_lam expr) = do +eta c expr | is_fun expr && not (is_lam expr) && all (== LambdaBody) c = do let arg_ty = (fst . Type.splitFunTy . CoreUtils.exprType) expr id <- Trans.lift $ mkInternalVar "param" arg_ty change (Lam id (App expr (Var id))) @@ -83,6 +85,48 @@ beta c expr = return expr -- Perform this transform everywhere betatop = everywhere ("beta", beta) +-------------------------------- +-- Case of known constructor simplification +-------------------------------- +-- If a case expressions scrutinizes a datacon application, we can +-- determine which alternative to use and remove the case alltogether. +-- We replace it with a let expression the binds every binder in the +-- alternative bound to the corresponding argument of the datacon. We do +-- this instead of substituting the binders, to prevent duplication of +-- work and preserve sharing wherever appropriate. +knowncase, knowncasetop :: Transform +knowncase context expr@(Case scrut@(App _ _) bndr ty alts) | not bndr_used = do + case collectArgs scrut of + (Var f, args) -> case Id.isDataConId_maybe f of + -- Not a dataconstructor? Don't change anything (probably a + -- function, then) + Nothing -> return expr + Just dc -> do + let (altcon, bndrs, res) = case List.find (\(altcon, bndrs, res) -> altcon == (DataAlt dc)) alts of + Just alt -> alt -- Return the alternative found + Nothing -> head alts -- If the datacon is not present, the first must be the default alternative + -- Double check if we have either the correct alternative, or + -- the default. + if altcon /= (DataAlt dc) && altcon /= DEFAULT then error ("Normalize.knowncase: Invalid core, datacon not found in alternatives and DEFAULT alternative is not first? " ++ pprString expr) else return () + -- Find out how many arguments to drop (type variables and + -- predicates like dictionaries). + let (tvs, preds, _, _) = DataCon.dataConSig dc + let count = length tvs + length preds + -- Create a let expression that binds each of the binders in + -- this alternative to the corresponding argument of the data + -- constructor. + let binds = zip bndrs (drop count args) + change $ Let (Rec binds) res + _ -> return expr -- Scrutinee is not an application of a var + where + is_used (_, _, expr) = expr_uses_binders [bndr] expr + bndr_used = or $ map is_used alts + +-- Leave all other expressions unchanged +knowncase c expr = return expr +-- Perform this transform everywhere +knowncasetop = everywhere ("knowncase", knowncase) + -------------------------------- -- Cast propagation -------------------------------- @@ -121,86 +165,55 @@ castsimpl c expr = return expr -- Perform this transform everywhere castsimpltop = everywhere ("castsimpl", castsimpl) - -------------------------------- --- Lambda simplication +-- Return value simplification -------------------------------- --- Ensure that a lambda always evaluates to a let expressions or a simple --- variable reference. -lambdasimpl, lambdasimpltop :: Transform --- Don't simplify a lambda that evaluates to let, since this is already --- normal form (and would cause infinite loops). -lambdasimpl c expr@(Lam _ (Let _ _)) = return expr --- Put the of a lambda in its own binding, but not when the expression is --- already a local variable, or not representable (to prevent loops with --- inlinenonrep). -lambdasimpl c expr@(Lam bndr res) = do - repr <- isRepr res - local_var <- Trans.lift $ is_local_var res +-- Ensure the return value of a function follows proper normal form. eta +-- expansion ensures the body starts with lambda abstractions, this +-- transformation ensures that the lambda abstractions always contain a +-- recursive let and that, when the return value is representable, the +-- let contains a local variable reference in its body. +retvalsimpl c expr | all (== LambdaBody) c && not (is_lam expr) && not (is_let expr) = do + local_var <- Trans.lift $ is_local_var expr + repr <- isRepr expr if not local_var && repr then do - id <- Trans.lift $ mkBinderFor res "res" - change $ Lam bndr (Let (NonRec id res) (Var id)) + id <- Trans.lift $ mkBinderFor expr "res" + change $ Let (Rec [(id, expr)]) (Var id) + else + return expr + +retvalsimpl c expr@(Let (Rec binds) body) | all (== LambdaBody) c = do + -- Don't extract values that are already a local variable, to prevent + -- loops with ourselves. + local_var <- Trans.lift $ is_local_var body + -- Don't extract values that are not representable, to prevent loops with + -- inlinenonrep + repr <- isRepr body + if not local_var && repr + then do + id <- Trans.lift $ mkBinderFor body "res" + change $ Let (Rec ((id, body):binds)) (Var id) else - -- If the result is already a local var or not representable, don't - -- extract it. return expr --- Leave all other expressions unchanged -lambdasimpl c expr = return expr --- Perform this transform everywhere -lambdasimpltop = everywhere ("lambdasimpl", lambdasimpl) --------------------------------- --- let derecursification --------------------------------- -letderec, letderectop :: Transform -letderec c expr@(Let (Rec binds) res) = case liftable of - -- Nothing is liftable, just return - [] -> return expr - -- Something can be lifted, generate a new let expression - _ -> change $ mkNonRecLets liftable (Let (Rec nonliftable) res) - where - -- Make a list of all the binders bound in this recursive let - bndrs = map fst binds - -- See which bindings are liftable - (liftable, nonliftable) = List.partition canlift binds - -- Any expression that does not use any of the binders in this recursive let - -- can be lifted into a nonrec let. It can't use its own binder either, - -- since that would mean the binding is self-recursive and should be in a - -- single bind recursive let. - canlift (bndr, e) = not $ expr_uses_binders bndrs e -- Leave all other expressions unchanged -letderec c expr = return expr +retvalsimpl c expr = return expr -- Perform this transform everywhere -letderectop = everywhere ("letderec", letderec) +retvalsimpltop = everywhere ("retvalsimpl", retvalsimpl) -------------------------------- --- let simplification +-- let derecursification -------------------------------- -letsimpl, letsimpltop :: Transform --- Don't simplify a let that evaluates to another let, since this is already --- normal form (and would cause infinite loops with letflat below). -letsimpl c expr@(Let _ (Let _ _)) = return expr --- Put the "in ..." value of a let in its own binding, but not when the --- expression is already a local variable, or not representable (to prevent loops with inlinenonrep). -letsimpl c expr@(Let binds res) = do - repr <- isRepr res - local_var <- Trans.lift $ is_local_var res - if not local_var && repr - then do - -- If the result is not a local var already (to prevent loops with - -- ourselves), extract it. - id <- Trans.lift $ mkBinderFor res "foo" - change $ Let binds (Let (NonRec id res) (Var id)) - else - -- If the result is already a local var, don't extract it. - return expr +letrec, letrectop :: Transform +letrec c expr@(Let (NonRec bndr val) res) = + change $ Let (Rec [(bndr, val)]) res -- Leave all other expressions unchanged -letsimpl c expr = return expr +letrec c expr = return expr -- Perform this transform everywhere -letsimpltop = everywhere ("letsimpl", letsimpl) +letrectop = everywhere ("letrec", letrec) -------------------------------- -- let flattening @@ -386,14 +399,14 @@ needsInline f = do (Var f, args) -> return $ Just body -- Body is more complicated, try normalizing it _ -> do - norm_maybe <- Trans.lift $ getNormalized_maybe f + norm_maybe <- Trans.lift $ getNormalized_maybe False f case norm_maybe of -- Noth normalizeable Nothing -> return Nothing - Just norm -> case splitNormalized norm of + Just norm -> case splitNormalizedNonRep norm of -- The function has just a single binding, so that's simple -- enough to inline. - (args, [bind], res) -> return $ Just norm + (args, [bind], Var res) -> return $ Just norm -- More complicated function, don't inline _ -> return Nothing @@ -601,12 +614,9 @@ casesimpl c expr@(Case scrut bndr ty alts) | not bndr_used = do -- inlinenonrep). if (not wild) && repr then do - -- Create on new binder that will actually capture a value in this + caseexpr <- Trans.lift $ mkSelCase scrut i + -- Create a new binder that will actually capture a value in this -- case statement, and return it. - let bty = (Id.idType b) - id <- Trans.lift $ mkInternalVar "sel" bty - let binders = take i wildbndrs ++ [id] ++ drop (i+1) wildbndrs - let caseexpr = Case scrut b bty [(con, binders, Var id)] return (wildbndrs!!i, Just (b, caseexpr)) else -- Just leave the original binder in place, and don't generate an @@ -769,6 +779,93 @@ argprop c expr = return expr -- Perform this transform everywhere argproptop = everywhere ("argprop", argprop) +-------------------------------- +-- Non-representable result inlining +-------------------------------- +-- This transformation takes a function that has a non-representable +-- result (e.g., a tuple containing a function, or an Integer. The +-- latter can occur in some cases as the result of the fromIntegerT +-- function) and inlines enough of the function to make the result +-- representable again. +-- +-- This is done by first normalizing the function and then "inlining" +-- the result. Since no unrepresentable let bindings are allowed in +-- normal form, we can be sure that all free variables of the result +-- expression will be representable (Note that we probably can't +-- guarantee that all representable parts of the expression will be free +-- variables, so we might inline more than strictly needed). +-- +-- The new function result will be a tuple containing all free variables +-- of the old result, so the old result can be rebuild at the caller. +inlinenonrepresult, inlinenonrepresulttop :: Transform + +-- Apply to any (application of) a reference to a top level function +-- that is fully applied (i.e., dos not have a function type) but is not +-- representable. We apply in any context, since non-representable +-- expressions are generally left alone and can occur anywhere. +inlinenonrepresult context expr | not (is_fun expr) = + case collectArgs expr of + (Var f, args) -> do + repr <- isRepr expr + if not repr + then do + body_maybe <- Trans.lift $ getNormalized_maybe True f + case body_maybe of + Just body -> do + let (bndrs, binds, res) = splitNormalizedNonRep body + -- Get the free local variables of res + global_bndrs <- Trans.lift getGlobalBinders + let interesting var = Var.isLocalVar var && (var `notElem` global_bndrs) + let free_vars = VarSet.varSetElems $ CoreFVs.exprSomeFreeVars interesting res + let free_var_types = map Id.idType free_vars + let n_free_vars = length free_vars + -- Get a tuple datacon to wrap around the free variables + let fvs_datacon = TysWiredIn.tupleCon BasicTypes.Boxed n_free_vars + let fvs_datacon_id = DataCon.dataConWorkId fvs_datacon + -- Let the function now return a tuple with references to + -- all free variables of the old return value. First pass + -- all the types of the variables, since tuple + -- constructors are polymorphic. + let newres = mkApps (Var fvs_datacon_id) (map Type free_var_types ++ map Var free_vars) + -- Recreate the function body with the changed return value + let newbody = mkLams bndrs (Let (Rec binds) newres) + -- Create the new function + f' <- Trans.lift $ mkFunction f newbody + + -- Call the new function + let newapp = mkApps (Var f') args + res_bndr <- Trans.lift $ mkBinderFor newapp "res" + -- Create extractor case expressions to extract each of the + -- free variables from the tuple. + sel_cases <- Trans.lift $ mapM (mkSelCase (Var res_bndr)) [0..n_free_vars-1] + + -- Bind the res_bndr to the result of the new application + -- and each of the free variables to the corresponding + -- selector case. Replace the let body with the original + -- body of the called function (which can still access all + -- of its free variables, from the let). + let binds = (res_bndr, newapp):(zip free_vars sel_cases) + let letexpr = Let (Rec binds) res + + -- Finally, regenarate all uniques in the new expression, + -- since the free variables could otherwise become + -- duplicated. It is not strictly necessary to regenerate + -- res, since we're moving that expression, but it won't + -- hurt. + letexpr_uniqued <- Trans.lift $ genUniques letexpr + change letexpr_uniqued + Nothing -> return expr + else + -- Don't touch representable expressions + return expr + -- Not a reference to or application of a top level function + _ -> return expr +-- Leave all other expressions unchanged +inlinenonrepresult c expr = return expr +-- Perform this transform everywhere +inlinenonrepresulttop = everywhere ("inlinenonrepresult", inlinenonrepresult) + + -------------------------------- -- Function-typed argument extraction -------------------------------- @@ -820,25 +917,6 @@ funextract c expr = return expr -- Perform this transform everywhere funextracttop = everywhere ("funextract", funextract) --------------------------------- --- Ensure that a function that just returns another function (or rather, --- another top-level binder) is still properly normalized. This is a temporary --- solution, we should probably integrate this pass with lambdasimpl and --- letsimpl instead. --------------------------------- -simplrestop c expr@(Lam _ _) = return expr -simplrestop c expr@(Let _ _) = return expr -simplrestop c expr = do - local_var <- Trans.lift $ is_local_var expr - -- Don't extract values that are not representable, to prevent loops with - -- inlinenonrep - repr <- isRepr expr - if local_var || not repr - then - return expr - else do - id <- Trans.lift $ mkBinderFor expr "res" - change $ Let (NonRec id expr) (Var id) -------------------------------- -- End of transformations -------------------------------- @@ -847,15 +925,16 @@ simplrestop c expr = do -- What transforms to run? -transforms = [inlinedicttop, inlinetopleveltop, classopresolutiontop, argproptop, funextracttop, etatop, betatop, castproptop, letremovesimpletop, letderectop, letremovetop, letsimpltop, letflattop, scrutsimpltop, scrutbndrremovetop, casesimpltop, caseremovetop, inlinenonreptop, appsimpltop, letremoveunusedtop, castsimpltop, lambdasimpltop, simplrestop] +transforms = [inlinedicttop, inlinetopleveltop, inlinenonrepresulttop, knowncasetop, classopresolutiontop, argproptop, funextracttop, etatop, betatop, castproptop, letremovesimpletop, letrectop, letremovetop, retvalsimpltop, letflattop, scrutsimpltop, scrutbndrremovetop, casesimpltop, caseremovetop, inlinenonreptop, appsimpltop, letremoveunusedtop, castsimpltop] -- | Returns the normalized version of the given function, or an error -- if it is not a known global binder. getNormalized :: - CoreBndr -- ^ The function to get + Bool -- ^ Allow the result to be unrepresentable? + -> CoreBndr -- ^ The function to get -> TranslatorSession CoreExpr -- The normalized function body -getNormalized bndr = do - norm <- getNormalized_maybe bndr +getNormalized result_nonrep bndr = do + norm <- getNormalized_maybe result_nonrep bndr return $ Maybe.fromMaybe (error $ "Normalize.getNormalized: Unknown or non-representable function requested: " ++ show bndr) norm @@ -863,27 +942,23 @@ getNormalized bndr = do -- | Returns the normalized version of the given function, or Nothing -- when the binder is not a known global binder or is not normalizeable. getNormalized_maybe :: - CoreBndr -- ^ The function to get + Bool -- ^ Allow the result to be unrepresentable? + -> CoreBndr -- ^ The function to get -> TranslatorSession (Maybe CoreExpr) -- The normalized function body -getNormalized_maybe bndr = do +getNormalized_maybe result_nonrep bndr = do expr_maybe <- getGlobalBind bndr - normalizeable <- isNormalizeable' bndr + normalizeable <- isNormalizeable result_nonrep bndr if not normalizeable || Maybe.isNothing expr_maybe then -- Binder not normalizeable or not found return Nothing - else if is_poly (Var bndr) - then - -- This should really only happen at the top level... TODO: Give - -- a different error if this happens down in the recursion. - error $ "\nNormalize.normalizeBind: Function " ++ show bndr ++ " is polymorphic, can't normalize" - else do - -- Binder found and is monomorphic. Normalize the expression - -- and cache the result. - normalized <- Utils.makeCached bndr tsNormalized $ - normalizeExpr (show bndr) (Maybe.fromJust expr_maybe) - return (Just normalized) + else do + -- Binder found and is monomorphic. Normalize the expression + -- and cache the result. + normalized <- Utils.makeCached bndr tsNormalized $ + normalizeExpr (show bndr) (Maybe.fromJust expr_maybe) + return (Just normalized) -- | Normalize an expression normalizeExpr :: @@ -892,22 +967,32 @@ normalizeExpr :: -> TranslatorSession CoreSyn.CoreExpr -- ^ The normalized expression normalizeExpr what expr = do + startcount <- MonadState.get tsTransformCounter expr_uniqued <- genUniques expr -- Normalize this expression trace (what ++ " before normalization:\n\n" ++ showSDoc ( ppr expr_uniqued ) ++ "\n") $ return () expr' <- dotransforms transforms expr_uniqued - trace ("\n" ++ what ++ " after normalization:\n\n" ++ showSDoc ( ppr expr')) $ return () - return expr' + endcount <- MonadState.get tsTransformCounter + trace ("\n" ++ what ++ " after normalization:\n\n" ++ showSDoc ( ppr expr') + ++ "\nNeeded " ++ show (endcount - startcount) ++ " transformations to normalize " ++ what) $ + return expr' -- | Split a normalized expression into the argument binders, top level --- bindings and the result binder. +-- bindings and the result binder. This function returns an error if +-- the type of the expression is not representable. splitNormalized :: CoreExpr -- ^ The normalized expression -> ([CoreBndr], [Binding], CoreBndr) -splitNormalized expr = (args, binds, res) +splitNormalized expr = + case splitNormalizedNonRep expr of + (args, binds, Var res) -> (args, binds, res) + _ -> error $ "Normalize.splitNormalized: Not in normal form: " ++ pprString expr ++ "\n" + +-- Split a normalized expression, whose type can be unrepresentable. +splitNormalizedNonRep:: + CoreExpr -- ^ The normalized expression + -> ([CoreBndr], [Binding], CoreExpr) +splitNormalizedNonRep expr = (args, binds, resexpr) where (args, letexpr) = CoreSyn.collectBinders expr (binds, resexpr) = flattenLets letexpr - res = case resexpr of - (Var x) -> x - _ -> error $ "Normalize.splitNormalized: Not in normal form: " ++ pprString expr ++ "\n"