Move the DesignFile creation to VHDL.
[matthijs/master-project/cλash.git] / Flatten.hs
index 8a230162daf6f43cf21036390c6a072ae261ce8d..12f6ee3be26cfa8d25cf778aa15a404ae11a5d2e 100644 (file)
@@ -7,6 +7,8 @@ import qualified Name
 import qualified Maybe
 import qualified DataCon
 import qualified CoreUtils
+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
@@ -23,27 +25,22 @@ dataConAppArgs dc args =
   where
     tycount = length $ DataCon.dataConAllTyVars dc
 
-genSignalUses ::
+genSignals ::
   Type.Type
-  -> FlattenState SignalUseMap
-
-genSignalUses ty = do
-  typeMapToUseMap tymap
+  -> FlattenState (SignalMap UnnamedSignal)
+
+genSignals ty =
+  -- First generate a map with the right structure containing the types, and
+  -- generate signals for each of them.
+  Traversable.mapM (\ty -> genSignalId SigInternal ty) (mkHsValueMap ty)
+
+-- | Marks a signal as the given SigUse, if its id is in the list of id's
+--   given.
+markSignal :: SigUse -> [UnnamedSignal] -> (UnnamedSignal, SignalInfo) -> (UnnamedSignal, SignalInfo)
+markSignal use ids (id, info) =
+  (id, info')
   where
-    -- First generate a map with the right structure containing the types
-    tymap = mkHsValueMap ty
-
-typeMapToUseMap ::
-  HsValueMap Type.Type
-  -> FlattenState SignalUseMap
-
-typeMapToUseMap (Single ty) = do
-  id <- genSignalId
-  return $ Single (SignalUse id)
-
-typeMapToUseMap (Tuple tymaps) = do
-  usemaps <- State.mapM typeMapToUseMap tymaps
-  return $ Tuple usemaps
+    info' = if id `elem` ids then info { sigUse = use} else info
 
 -- | Flatten a haskell function
 flattenFunction ::
@@ -53,26 +50,28 @@ flattenFunction ::
 
 flattenFunction _ (Rec _) = error "Recursive binders not supported"
 flattenFunction hsfunc bind@(NonRec var expr) =
-  FlatFunction args res apps conds
+  FlatFunction args res apps conds sigs'
   where
-    init_state        = ([], [], 0)
+    init_state        = ([], [], [], 0)
     (fres, end_state) = State.runState (flattenExpr [] expr) init_state
     (args, res)       = fres
-    (apps, conds, _)  = end_state
+    portlist          = concat (map Foldable.toList (res:args))
+    (apps, conds, sigs, _)  = end_state
+    sigs'             = fmap (markSignal SigPort portlist) sigs
 
 flattenExpr ::
   BindMap
   -> CoreExpr
-  -> FlattenState ([SignalDefMap], SignalUseMap)
+  -> FlattenState ([SignalMap UnnamedSignal], (SignalMap UnnamedSignal))
 
 flattenExpr binds lam@(Lam b expr) = do
   -- Find the type of the binder
   let (arg_ty, _) = Type.splitFunTy (CoreUtils.exprType lam)
   -- Create signal names for the binder
-  defs <- genSignalUses arg_ty
+  defs <- genSignals arg_ty
   let binds' = (b, Left defs):binds
   (args, res) <- flattenExpr binds' expr
-  return ((useMapToDefMap defs) : args, res)
+  return (defs : args, res)
 
 flattenExpr binds (Var id) =
   case bind of
@@ -114,12 +113,12 @@ flattenExpr binds app@(App _ _) = do
       -- Check and split each of the arguments
       let (_, arg_ress) = unzip (zipWith checkArg args flat_args)
       -- Generate signals for our result
-      res <- genSignalUses ty
+      res <- genSignals ty
       -- Create the function application
       let app = FApp {
         appFunc = func,
         appArgs = arg_ress,
-        appRes  = useMapToDefMap res
+        appRes  = res
       }
       addApp app
       return ([], res)
@@ -154,7 +153,7 @@ flattenExpr binds expr@(Case (Var v) b _ alts) =
       -> Var.Var                -- The scrutinee
       -> CoreBndr               -- The binder to bind the scrutinee to
       -> CoreAlt                -- The single alternative
-      -> FlattenState ( [SignalDefMap], SignalUseMap)
+      -> FlattenState ( [SignalMap UnnamedSignal], SignalMap UnnamedSignal)
                                            -- See expandExpr
     flattenSingleAltCaseExpr binds v b alt@(DataAlt datacon, bind_vars, expr) =
       if not (DataCon.isTupleCon datacon) 
@@ -194,4 +193,39 @@ appToHsFunction ty f args =
     hsargs = map (useAsPort . mkHsValueMap . CoreUtils.exprType) args
     hsres  = useAsPort (mkHsValueMap ty)
 
+-- | Translates signal id's to SignalInfo for any signals used as state.
+findState ::
+  [(UnnamedSignal, SignalInfo)] -- | A map of id to info
+  -> UnnamedSignal              -- | The signal id to look at
+  -> HsValueUse                 -- | How is this signal used?
+  -> Maybe (Int, SignalInfo)    -- | The state num and SignalInfo, if appropriate
+
+findState sigs id (State num) = 
+  Just (num, Maybe.fromJust $ lookup id sigs)
+findState _ _ _ = Nothing
+
+
+-- | Returns pairs of signals that should be mapped to state in this function.
+getOwnStates ::
+  HsFunction                      -- | The function to look at
+  -> FlatFunction                 -- | The function to look at
+  -> [(Int, SignalInfo, SignalInfo)]   
+        -- | The state signals. The first is the state number, the second the
+        --   signal to assign the current state to, the last is the signal
+        --   that holds the new state.
+
+getOwnStates hsfunc flatfunc =
+  [(old_num, old_info, new_info) 
+    | (old_num, old_info) <- args_states
+    , (new_num, new_info) <- res_states
+    , old_num == new_num]
+  where
+    sigs = flat_sigs flatfunc
+    -- Translate args and res to lists of (statenum, SignalInfo)
+    args = zipWith (zipValueMapsWith $ findState sigs) (flat_args flatfunc) (hsFuncArgs hsfunc)
+    args_states = Maybe.catMaybes $ concat $ map Foldable.toList $ args
+    res = zipValueMapsWith (findState sigs) (flat_res flatfunc) (hsFuncRes hsfunc)
+    res_states = Maybe.catMaybes $ Foldable.toList res
+
+    
 -- vim: set ts=8 sw=2 sts=2 expandtab: