X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=c%CE%BBash%2FCLasH%2FNormalize.hs;h=dc3c0c2052141045c09b53f6af5af42012a50d6d;hb=c29a9d04d534beedb2221a03f672310af16dd0cd;hp=75ab7380f0bca63f40bac1c4f423ef356e8c2c19;hpb=9ebf03351aaec723053b7911aac922fbf2417756;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 75ab738..dc3c0c2 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 @@ -53,19 +56,18 @@ import CLasH.Utils.Pretty -- 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 +eta :: Transform 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))) -- Leave all other expressions unchanged eta c e = return e -etatop = everywhere ("eta", eta) -------------------------------- -- β-reduction -------------------------------- -beta, betatop :: Transform +beta :: Transform -- Substitute arg for x in expr. For value lambda's, also clone before -- substitution. beta c (App (Lam x expr) arg) | CoreSyn.isTyVar x = setChanged >> substitute x arg c expr @@ -79,28 +81,64 @@ beta c (App (Case scrut b ty alts) arg) = change $ Case scrut b ty' alts' ty' = CoreUtils.applyTypeToArg ty arg -- Leave all other expressions unchanged 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 :: 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 -------------------------------- -- Cast propagation -------------------------------- -- Try to move casts as much downward as possible. -castprop, castproptop :: Transform +castprop :: Transform castprop c (Cast (Let binds expr) ty) = change $ Let binds (Cast expr ty) castprop c expr@(Cast (Case scrut b _ alts) ty) = change (Case scrut b ty alts') where alts' = map (\(con, bndrs, expr) -> (con, bndrs, (Cast expr ty))) alts -- Leave all other expressions unchanged castprop c expr = return expr --- Perform this transform everywhere -castproptop = everywhere ("castprop", castprop) -------------------------------- -- Cast simplification. Mostly useful for state packing and unpacking, but -- perhaps for others as well. -------------------------------- -castsimpl, castsimpltop :: Transform +castsimpl :: Transform castsimpl c expr@(Cast val ty) = do -- Don't extract values that are already simpl local_var <- Trans.lift $ is_local_var val @@ -117,15 +155,25 @@ castsimpl c expr@(Cast val ty) = do return expr -- Leave all other expressions unchanged castsimpl c expr = return expr --- Perform this transform everywhere -castsimpltop = everywhere ("castsimpl", castsimpl) -------------------------------- --- 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. +-- Return value simplification -------------------------------- +-- 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 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. @@ -140,32 +188,19 @@ retvalsimpl c expr@(Let (Rec binds) body) | all (== LambdaBody) c = do else return expr -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 expr "res" - change $ Let (Rec [(id, expr)]) (Var id) - else - return expr -- Leave all other expressions unchanged retvalsimpl c expr = return expr --- Perform this transform everywhere -retvalsimpltop = everywhere ("retvalsimpl", retvalsimpl) -------------------------------- -- let derecursification -------------------------------- -letrec, letrectop :: Transform +letrec :: Transform letrec c expr@(Let (NonRec bndr val) res) = change $ Let (Rec [(bndr, val)]) res -- Leave all other expressions unchanged letrec c expr = return expr --- Perform this transform everywhere -letrectop = everywhere ("letrec", letrec) -------------------------------- -- let flattening @@ -175,7 +210,7 @@ letrectop = everywhere ("letrec", letrec) -- let b = (let b' = expr' in res') in res -- to: -- let b' = expr' in (let b = res' in res) -letflat, letflattop :: Transform +letflat :: Transform -- Turn a nonrec let that binds a let into two nested lets. letflat c (Let (NonRec b (Let binds res')) res) = change $ Let binds (Let (NonRec b res') res) @@ -195,31 +230,27 @@ letflat c (Let (Rec binds) expr) = do flatbind (b, expr) = return [(b, expr)] -- Leave all other expressions unchanged letflat c expr = return expr --- Perform this transform everywhere -letflattop = everywhere ("letflat", letflat) -------------------------------- -- empty let removal -------------------------------- -- Remove empty (recursive) lets -letremove, letremovetop :: Transform +letremove :: Transform letremove c (Let (Rec []) res) = change res -- Leave all other expressions unchanged letremove c expr = return expr --- Perform this transform everywhere -letremovetop = everywhere ("letremove", letremove) -------------------------------- -- Simple let binding removal -------------------------------- -- Remove a = b bindings from let expressions everywhere -letremovesimpletop :: Transform -letremovesimpletop = everywhere ("letremovesimple", inlinebind (\(b, e) -> Trans.lift $ is_local_var e)) +letremovesimple :: Transform +letremovesimple = inlinebind (\(b, e) -> Trans.lift $ is_local_var e) -------------------------------- -- Unused let binding removal -------------------------------- -letremoveunused, letremoveunusedtop :: Transform +letremoveunused :: Transform letremoveunused c expr@(Let (NonRec b bound) res) = do let used = expr_uses_binders [b] res if used @@ -237,7 +268,6 @@ letremoveunused c expr@(Let (Rec binds) res) = do dobind (bndr, _) = any (expr_uses_binders [bndr]) (res:bound_exprs) -- Leave all other expressions unchanged letremoveunused c expr = return expr -letremoveunusedtop = everywhere ("letremoveunused", letremoveunused) {- -------------------------------- @@ -246,7 +276,7 @@ letremoveunusedtop = everywhere ("letremoveunused", letremoveunused) -- Merge two bindings in a let if they are identical -- TODO: We would very much like to use GHC's CSE module for this, but that -- doesn't track if something changed or not, so we can't use it properly. -letmerge, letmergetop :: Transform +letmerge :: Transform letmerge c expr@(Let _ _) = do let (binds, res) = flattenLets expr binds' <- domerge binds @@ -269,7 +299,6 @@ letmerge c expr@(Let _ _) = do | otherwise = return (b2, e2) -- Leave all other expressions unchanged letmerge c expr = return expr -letmergetop = everywhere ("letmerge", letmerge) -} -------------------------------- @@ -286,8 +315,8 @@ letmergetop = everywhere ("letmerge", letmerge) -- transformations will just not work on those function-typed values at first, -- but the other transformations (in particular β-reduction) should make sure -- that the type of those values eventually becomes representable. -inlinenonreptop :: Transform -inlinenonreptop = everywhere ("inlinenonrep", inlinebind ((Monad.liftM not) . isRepr . snd)) +inlinenonrep :: Transform +inlinenonrep = inlinebind ((Monad.liftM not) . isRepr . snd) -------------------------------- -- Top level function inlining @@ -317,7 +346,7 @@ inlinenonreptop = everywhere ("inlinenonrep", inlinebind ((Monad.liftM not) . is -- that will eventually generate instantiations of trivial components. -- By not inlining any other reference, we also prevent looping problems -- with funextract and inlinedict. -inlinetoplevel, inlinetopleveltop :: Transform +inlinetoplevel :: Transform inlinetoplevel (LetBinding:_) expr | not (is_fun expr) = case collectArgs expr of (Var f, args) -> do @@ -335,8 +364,7 @@ inlinetoplevel (LetBinding:_) expr | not (is_fun expr) = -- Leave all other expressions unchanged inlinetoplevel c expr = return expr -inlinetopleveltop = everywhere ("inlinetoplevel", inlinetoplevel) - + -- | Does the given binder need to be inlined? If so, return the body to -- be used for inlining. needsInline :: CoreBndr -> TransformMonad (Maybe CoreExpr) @@ -351,17 +379,17 @@ 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 - + -------------------------------- -- Dictionary inlining -------------------------------- @@ -387,7 +415,6 @@ inlinedict c expr@(App (App (Var sel) ty) (Var dict)) | not is_builtin && is_cla -- Leave all other expressions unchanged inlinedict c expr = return expr -inlinedicttop = everywhere ("inlinedict", inlinedict) -------------------------------- -- ClassOp resolution @@ -423,7 +450,7 @@ inlinedicttop = everywhere ("inlinedict", inlinedict) -- translateable. For example, when deriving ==, GHC generates code -- using $con2tag functions to translate a datacon to an int and compare -- that with GHC.Prim.==# . Better to avoid that for now. -classopresolution, classopresolutiontop :: Transform +classopresolution :: Transform classopresolution c expr@(App (App (Var sel) ty) dict) | not is_builtin = case Id.isClassOpId_maybe sel of -- Not a class op selector @@ -450,13 +477,11 @@ classopresolution c expr@(App (App (Var sel) ty) dict) | not is_builtin = -- Leave all other expressions unchanged classopresolution c expr = return expr --- Perform this transform everywhere -classopresolutiontop = everywhere ("classopresolution", classopresolution) -------------------------------- -- Scrutinee simplification -------------------------------- -scrutsimpl,scrutsimpltop :: Transform +scrutsimpl :: Transform -- Don't touch scrutinees that are already simple scrutsimpl c expr@(Case (Var _) _ _ _) = return expr -- Replace all other cases with a let that binds the scrutinee and a new @@ -473,8 +498,6 @@ scrutsimpl c expr@(Case scrut b ty alts) = do return expr -- Leave all other expressions unchanged scrutsimpl c expr = return expr --- Perform this transform everywhere -scrutsimpltop = everywhere ("scrutsimpl", scrutsimpl) -------------------------------- -- Scrutinee binder removal @@ -484,7 +507,7 @@ scrutsimpltop = everywhere ("scrutsimpl", scrutsimpl) -- arguments. Since strictness does not matter for us (rather, everything is -- sort of strict), this binder is ignored when generating VHDL, and must thus -- be wild in the normal form. -scrutbndrremove, scrutbndrremovetop :: Transform +scrutbndrremove :: Transform -- If the scrutinee is already simple, and the bndr is not wild yet, replace -- all occurences of the binder with the scrutinee variable. scrutbndrremove c (Case (Var scrut) bndr ty alts) | bndr_used = do @@ -499,12 +522,11 @@ scrutbndrremove c (Case (Var scrut) bndr ty alts) | bndr_used = do wild = MkCore.mkWildBinder (Id.idType bndr) -- Leave all other expressions unchanged scrutbndrremove c expr = return expr -scrutbndrremovetop = everywhere ("scrutbndrremove", scrutbndrremove) -------------------------------- -- Case binder wildening -------------------------------- -casesimpl, casesimpltop :: Transform +casesimpl :: Transform -- This is already a selector case (or, if x does not appear in bndrs, a very -- simple case statement that will be removed by caseremove below). Just leave -- it be. @@ -566,12 +588,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 @@ -598,29 +617,25 @@ casesimpl c expr@(Case scrut bndr ty alts) | not bndr_used = do return (Nothing, expr) -- Leave all other expressions unchanged casesimpl c expr = return expr --- Perform this transform everywhere -casesimpltop = everywhere ("casesimpl", casesimpl) -------------------------------- -- Case removal -------------------------------- -- Remove case statements that have only a single alternative and only wild -- binders. -caseremove, caseremovetop :: Transform +caseremove :: Transform -- Replace a useless case by the value of its single alternative caseremove c (Case scrut b ty [(con, bndrs, expr)]) | not usesvars = change expr -- Find if any of the binders are used by expr where usesvars = (not . VarSet.isEmptyVarSet . (CoreFVs.exprSomeFreeVars (`elem` b:bndrs))) expr -- Leave all other expressions unchanged caseremove c expr = return expr --- Perform this transform everywhere -caseremovetop = everywhere ("caseremove", caseremove) -------------------------------- -- Argument extraction -------------------------------- -- Make sure that all arguments of a representable type are simple variables. -appsimpl, appsimpltop :: Transform +appsimpl :: Transform -- Simplify all representable arguments. Do this by introducing a new Let -- that binds the argument and passing the new binder in the application. appsimpl c expr@(App f arg) = do @@ -635,8 +650,6 @@ appsimpl c expr@(App f arg) = do return expr -- Leave all other expressions unchanged appsimpl c expr = return expr --- Perform this transform everywhere -appsimpltop = everywhere ("appsimpl", appsimpl) -------------------------------- -- Function-typed argument propagation @@ -644,7 +657,7 @@ appsimpltop = everywhere ("appsimpl", appsimpl) -- Remove all applications to function-typed arguments, by duplication the -- function called with the function-typed parameter replaced by the free -- variables of the argument passed in. -argprop, argproptop :: Transform +argprop :: Transform -- Transform any application of a named function (i.e., skip applications of -- lambda's). Also skip applications that have arguments with free type -- variables, since we can't inline those. @@ -731,8 +744,105 @@ argprop c expr@(App _ _) | is_var fexpr = do return ([arg], [id], mkReferenceTo id) -- Leave all other expressions unchanged argprop c expr = return expr --- Perform this transform everywhere -argproptop = everywhere ("argprop", argprop) + +-------------------------------- +-- Non-representable result inlining +-------------------------------- +-- This transformation takes a function (top level binding) 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. +-- +-- We take care not to inline dictionary id's, which are top level +-- bindings with a non-representable result type as well, since those +-- will never become VHDL signals directly. There is a separate +-- transformation (inlinedict) that specifically inlines dictionaries +-- only when it is useful. +inlinenonrepresult :: 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) | not (Id.isDictId f) -> 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 + if has_free_tyvars res + then + -- Don't touch anything with free type variables, since + -- we can't return those. We'll wait until argprop + -- removed those variables. + return expr + else do + -- 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 or (applications of) + -- dictionary ids. + 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 + -------------------------------- -- Function-typed argument extraction @@ -742,7 +852,7 @@ argproptop = everywhere ("argprop", argprop) -- puts it in a brand new top level binder. This allows us to for example -- apply map to a lambda expression This will not conflict with inlinenonrep, -- since that only inlines local let bindings, not top level bindings. -funextract, funextracttop :: Transform +funextract :: Transform funextract c expr@(App _ _) | is_var fexpr = do body_maybe <- Trans.lift $ getGlobalBind f case body_maybe of @@ -782,8 +892,6 @@ funextract c expr@(App _ _) | is_var fexpr = do -- Leave all other expressions unchanged funextract c expr = return expr --- Perform this transform everywhere -funextracttop = everywhere ("funextract", funextract) -------------------------------- -- End of transformations @@ -793,15 +901,39 @@ funextracttop = everywhere ("funextract", funextract) -- What transforms to run? -transforms = [inlinedicttop, inlinetopleveltop, classopresolutiontop, argproptop, funextracttop, etatop, betatop, castproptop, letremovesimpletop, letrectop, letremovetop, retvalsimpltop, letflattop, scrutsimpltop, scrutbndrremovetop, casesimpltop, caseremovetop, inlinenonreptop, appsimpltop, letremoveunusedtop, castsimpltop] +transforms = [ ("inlinedict", inlinedict) + , ("inlinetoplevel", inlinetoplevel) + , ("inlinenonrepresult", inlinenonrepresult) + , ("knowncase", knowncase) + , ("classopresolution", classopresolution) + , ("argprop", argprop) + , ("funextract", funextract) + , ("eta", eta) + , ("beta", beta) + , ("castprop", castprop) + , ("letremovesimple", letremovesimple) + , ("letrec", letrec) + , ("letremove", letremove) + , ("retvalsimpl", retvalsimpl) + , ("letflat", letflat) + , ("scrutsimpl", scrutsimpl) + , ("scrutbndrremove", scrutbndrremove) + , ("casesimpl", casesimpl) + , ("caseremove", caseremove) + , ("inlinenonrep", inlinenonrep) + , ("appsimpl", appsimpl) + , ("letremoveunused", letremoveunused) + , ("castsimpl", castsimpl) + ] -- | 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 @@ -809,27 +941,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 :: @@ -849,14 +977,21 @@ normalizeExpr what expr = do 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"