Remove type parameterisation of SignalMap.
[matthijs/master-project/cλash.git] / Flatten.hs
index 2e66e90d1dbdb40b70324223423bbfedc07c4857..4194904c046ea211fbd83a6f0b7978f737415d80 100644 (file)
@@ -5,6 +5,7 @@ import qualified Var
 import qualified Type
 import qualified Name
 import qualified Maybe
+import qualified Control.Arrow as Arrow
 import qualified DataCon
 import qualified CoreUtils
 import qualified Data.Traversable as Traversable
@@ -27,7 +28,7 @@ dataConAppArgs dc args =
 
 genSignals ::
   Type.Type
-  -> FlattenState (SignalMap UnnamedSignal)
+  -> FlattenState SignalMap
 
 genSignals ty =
   -- First generate a map with the right structure containing the types, and
@@ -36,12 +37,15 @@ genSignals 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) =
+markSignals :: SigUse -> [SignalId] -> (SignalId, SignalInfo) -> (SignalId, SignalInfo)
+markSignals use ids (id, info) =
   (id, info')
   where
     info' = if id `elem` ids then info { sigUse = use} else info
 
+markSignal :: SigUse -> SignalId -> (SignalId, SignalInfo) -> (SignalId, SignalInfo)
+markSignal use id = markSignals use [id]
+
 -- | Flatten a haskell function
 flattenFunction ::
   HsFunction                      -- ^ The function to flatten
@@ -50,19 +54,27 @@ flattenFunction ::
 
 flattenFunction _ (Rec _) = error "Recursive binders not supported"
 flattenFunction hsfunc bind@(NonRec var expr) =
-  FlatFunction args res apps conds sigs'
+  FlatFunction args res apps conds sigs''''
   where
     init_state        = ([], [], [], 0)
     (fres, end_state) = State.runState (flattenExpr [] expr) init_state
-    (args, res)       = fres
-    portlist          = concat (map Foldable.toList (res:args))
     (apps, conds, sigs, _)  = end_state
-    sigs'             = fmap (markSignal SigPort portlist) sigs
+    (args, res)       = fres
+    arg_ports         = concat (map Foldable.toList args)
+    res_ports         = Foldable.toList res
+    -- Mark args and result signals as input and output ports resp.
+    sigs'             = fmap (markSignals SigPortIn arg_ports) sigs
+    sigs''            = fmap (markSignals SigPortOut res_ports) sigs'
+    -- Mark args and result states as old and new state resp.
+    args_states       = concat $ zipWith stateList (hsFuncArgs hsfunc) args
+    sigs'''           = foldl (\s (num, id) -> map (markSignal (SigStateOld num) id) s) sigs'' args_states
+    res_states        = stateList (hsFuncRes hsfunc) res
+    sigs''''          = foldl (\s (num, id) -> map (markSignal (SigStateNew num) id) s) sigs''' res_states
 
 flattenExpr ::
   BindMap
   -> CoreExpr
-  -> FlattenState ([SignalMap UnnamedSignal], (SignalMap UnnamedSignal))
+  -> FlattenState ([SignalMap], SignalMap)
 
 flattenExpr binds lam@(Lam b expr) = do
   -- Find the type of the binder
@@ -153,7 +165,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 ( [SignalMap UnnamedSignal], SignalMap UnnamedSignal)
+      -> FlattenState ( [SignalMap], SignalMap)
                                            -- See expandExpr
     flattenSingleAltCaseExpr binds v b alt@(DataAlt datacon, bind_vars, expr) =
       if not (DataCon.isTupleCon datacon) 
@@ -193,4 +205,50 @@ appToHsFunction ty f args =
     hsargs = map (useAsPort . mkHsValueMap . CoreUtils.exprType) args
     hsres  = useAsPort (mkHsValueMap ty)
 
+-- | Filters non-state signals and returns the state number and signal id for
+--   state values.
+filterState ::
+  SignalId                       -- | The signal id to look at
+  -> HsValueUse                  -- | How is this signal used?
+  -> Maybe (Int, SignalId )      -- | The state num and signal id, if this
+                                 --   signal was used as state
+
+filterState id (State num) = 
+  Just (num, id)
+filterState _ _ = Nothing
+
+-- | Returns a list of the state number and signal id of all used-as-state
+--   signals in the given maps.
+stateList ::
+  HsUseMap
+  -> (SignalMap)
+  -> [(Int, SignalId)]
+
+stateList uses signals =
+    Maybe.catMaybes $ Foldable.toList $ zipValueMapsWith filterState signals uses
+  
+-- | 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, sigid)
+    args = concat $ zipWith stateList (hsFuncArgs hsfunc) (flat_args flatfunc)
+    res = stateList (hsFuncRes hsfunc) (flat_res flatfunc)
+    -- Replace the second tuple element with the corresponding SignalInfo
+    args_states = map (Arrow.second $ signalInfo sigs) args
+    res_states = map (Arrow.second $ signalInfo sigs) res
+
+    
 -- vim: set ts=8 sw=2 sts=2 expandtab: