Remove two debug traces.
[matthijs/master-project/cλash.git] / cλash / CLasH / Normalize.hs
index 85be0d0ef61ae37050835a9784185a538db04990..d6acc13b19dbc82e37ffaa08195421c63e1f4e52 100644 (file)
@@ -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
@@ -82,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
 --------------------------------
@@ -354,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
             
@@ -569,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
@@ -737,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
 --------------------------------
@@ -796,15 +925,16 @@ 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 = [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
@@ -812,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 ::
@@ -852,14 +978,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"