Really revert all of the recent rotating changes.
[matthijs/master-project/cλash.git] / Flatten.hs
index 4bb6e71b268fd140c7f60df47754f12c9dffa6c8..d25ef73aceabb2feec43007b1a469b267a72ce09 100644 (file)
@@ -8,6 +8,7 @@ import qualified Maybe
 import qualified Control.Arrow as Arrow
 import qualified DataCon
 import qualified TyCon
+import qualified Literal
 import qualified CoreUtils
 import qualified TysWiredIn
 import qualified IdInfo
@@ -15,11 +16,12 @@ import qualified Data.Traversable as Traversable
 import qualified Data.Foldable as Foldable
 import Control.Applicative
 import Outputable ( showSDoc, ppr )
-import qualified Control.Monad.State as State
+import qualified Control.Monad.Trans.State as State
 
 import HsValueMap
 import TranslatorTypes
 import FlattenTypes
+import CoreTools
 
 -- Extract the arguments from a data constructor application (that is, the
 -- normal args, leaving out the type args).
@@ -52,11 +54,10 @@ markSignal use id = markSignals use [id]
 -- | Flatten a haskell function
 flattenFunction ::
   HsFunction                      -- ^ The function to flatten
-  -> CoreBind                     -- ^ The function value
+  -> (CoreBndr, CoreExpr)         -- ^ The function value
   -> FlatFunction                 -- ^ The resulting flat function
 
-flattenFunction _ (Rec _) = error "Recursive binders not supported"
-flattenFunction hsfunc bind@(NonRec var expr) =
+flattenFunction hsfunc (var, expr) =
   FlatFunction args res defs sigs
   where
     init_state        = ([], [], 0)
@@ -167,8 +168,11 @@ flattenExpr binds var@(Var id) =
           sig_id <- genSignalId SigInternal ty
           -- Add a name hint to the signal
           addNameHint (Name.getOccString id) sig_id
-          addDef (UncondDef (Right $ Literal lit) sig_id)
+          addDef (UncondDef (Right $ Literal lit Nothing) sig_id)
           return ([], Single sig_id)
+    IdInfo.VanillaGlobal ->
+      -- Treat references to globals as an application with zero elements
+      flattenApplicationExpr binds (CoreUtils.exprType var) id []
     otherwise ->
       error $ "Ids other than local vars and dataconstructors not supported: " ++ (showSDoc $ ppr id)
 
@@ -203,6 +207,23 @@ flattenExpr binds app@(App _ _) = do
         ([], b) <- flattenExpr binds (last args)
         res <- mkEqComparisons a b
         return ([], res)
+      else if fname == "fromInteger" then do
+        let [to_ty, to_dict, val] = args 
+        -- We assume this is an application of the GHC.Integer.smallInteger
+        -- function to a literal
+        let App smallint (Lit lit) = val
+        let (Literal.MachInt int) = lit
+        let ty = CoreUtils.exprType app
+        sig_id <- genSignalId SigInternal ty
+        -- TODO: fromInteger is defined for more types than just SizedWord
+        let len = sized_word_len ty
+        -- Use a to_unsigned to translate the number (a natural) to an unsiged
+        -- (array of bits)
+        let lit_str = "to_unsigned(" ++ (show int) ++ ", " ++ (show len) ++ ")"
+        -- Set the signal to our literal unconditionally, but add the type so
+        -- the literal will be typecast to the proper type.
+        addDef $ UncondDef (Right $ Literal lit_str (Just ty)) sig_id
+        return ([], Single sig_id)
       else
         flattenApplicationExpr binds (CoreUtils.exprType app) f args
   where
@@ -222,42 +243,12 @@ flattenExpr binds app@(App _ _) = do
 
     flattenBuildTupleExpr binds args = do
       -- Flatten each of our args
-      flat_args <- (State.mapM (flattenExpr binds) args)
+      flat_args <- (mapM (flattenExpr binds) args)
       -- Check and split each of the arguments
       let (_, arg_ress) = unzip (zipWith checkArg args flat_args)
       let res = Tuple arg_ress
       return ([], res)
 
-    -- | Flatten a normal application expression
-    flattenApplicationExpr binds ty f args = do
-      -- Find the function to call
-      let func = appToHsFunction ty f args
-      -- Flatten each of our args
-      flat_args <- (State.mapM (flattenExpr binds) args)
-      -- Check and split each of the arguments
-      let (_, arg_ress) = unzip (zipWith checkArg args flat_args)
-      -- Generate signals for our result
-      res <- genSignals ty
-      -- Add name hints to the generated signals
-      let resname = Name.getOccString f ++ "_res"
-      Traversable.mapM (addNameHint resname) res
-      -- Create the function application
-      let app = FApp {
-        appFunc = func,
-        appArgs = arg_ress,
-        appRes  = res
-      }
-      addDef app
-      return ([], res)
-    -- | Check a flattened expression to see if it is valid to use as a
-    --   function argument. The first argument is the original expression for
-    --   use in the error message.
-    checkArg arg flat =
-      let (args, res) = flat in
-      if not (null args)
-        then error $ "Passing lambda expression or function as a function argument not supported: " ++ (showSDoc $ ppr arg)
-        else flat 
-
 flattenExpr binds l@(Let (NonRec b bexpr) expr) = do
   (b_args, b_res) <- flattenExpr binds bexpr
   if not (null b_args)
@@ -276,11 +267,12 @@ flattenExpr binds expr@(Case scrut b _ alts) = do
   -- TODO: Special casing for higher order functions
   -- Flatten the scrutinee
   (_, res) <- flattenExpr binds scrut
+  -- Put the scrutinee in the BindMap
+  let binds' = (b, Left res) : binds
   case alts of
-    -- TODO include b in the binds list
-    [alt] -> flattenSingleAltCaseExpr binds res b alt
+    [alt] -> flattenSingleAltCaseExpr binds' res b alt
     -- Reverse the alternatives, so the __DEFAULT alternative ends up last
-    otherwise -> flattenMultipleAltCaseExpr binds res b (reverse alts)
+    otherwise -> flattenMultipleAltCaseExpr binds' res b (reverse alts)
   where
     flattenSingleAltCaseExpr ::
       BindMap
@@ -369,6 +361,36 @@ flattenExpr binds expr@(Case scrut b _ alts) = do
 flattenExpr _ expr = do
   error $ "Unsupported expression: " ++ (showSDoc $ ppr expr)
 
+-- | Flatten a normal application expression
+flattenApplicationExpr binds ty f args = do
+  -- Find the function to call
+  let func = appToHsFunction ty f args
+  -- Flatten each of our args
+  flat_args <- (mapM (flattenExpr binds) args)
+  -- Check and split each of the arguments
+  let (_, arg_ress) = unzip (zipWith checkArg args flat_args)
+  -- Generate signals for our result
+  res <- genSignals ty
+  -- Add name hints to the generated signals
+  let resname = Name.getOccString f ++ "_res"
+  Traversable.mapM (addNameHint resname) res
+  -- Create the function application
+  let app = FApp {
+    appFunc = func,
+    appArgs = arg_ress,
+    appRes  = res
+  }
+  addDef app
+  return ([], res)
+-- | Check a flattened expression to see if it is valid to use as a
+--   function argument. The first argument is the original expression for
+--   use in the error message.
+checkArg arg flat =
+  let (args, res) = flat in
+  if not (null args)
+    then error $ "Passing lambda expression or function as a function argument not supported: " ++ (showSDoc $ ppr arg)
+    else flat 
+
 -- | Translates a dataconstructor without arguments to the corresponding
 --   literal.
 dataConToLiteral :: DataCon.DataCon -> FlattenState String