Learn flattenExpr about function application.
[matthijs/master-project/cλash.git] / Flatten.hs
index 3c5fda7b9537a801915b23ff0472720179127327..7ce63a536a40595211a59e8888e065adf4931080 100644 (file)
@@ -1,5 +1,12 @@
 module Flatten where
 import CoreSyn
+import qualified Type
+import qualified Name
+import qualified TyCon
+import qualified Maybe
+import qualified DataCon
+import qualified CoreUtils
+import Outputable ( showSDoc, ppr )
 import qualified Control.Monad.State as State
 
 -- | A datatype that maps each of the single values in a haskell structure to
@@ -8,29 +15,61 @@ import qualified Control.Monad.State as State
 data HsValueMap mapto =
   Tuple [HsValueMap mapto]
   | Single mapto
-  | Unused
   deriving (Show, Eq)
 
+
+
+-- | Creates a HsValueMap with the same structure as the given type, using the
+--   given function for mapping the single types.
+mkHsValueMap ::
+  Type.Type                         -- ^ The type to map to a HsValueMap
+  -> HsValueMap Type.Type           -- ^ The resulting map and state
+
+mkHsValueMap ty =
+  case Type.splitTyConApp_maybe ty of
+    Just (tycon, args) ->
+      if (TyCon.isTupleTyCon tycon) 
+        then
+          Tuple (map mkHsValueMap args)
+        else
+          Single ty
+    Nothing -> Single ty
+
+-- Extract the arguments from a data constructor application (that is, the
+-- normal args, leaving out the type args).
+dataConAppArgs :: DataCon.DataCon -> [CoreExpr] -> [CoreExpr]
+dataConAppArgs dc args =
+    drop tycount args
+  where
+    tycount = length $ DataCon.dataConAllTyVars dc
+
+
+
 data FlatFunction = FlatFunction {
   args   :: [SignalDefMap],
   res    :: SignalUseMap,
   --sigs   :: [SignalDef],
-  apps   :: [App],
+  apps   :: [FApp],
   conds  :: [CondDef]
 } deriving (Show, Eq)
     
 type SignalUseMap = HsValueMap SignalUse
 type SignalDefMap = HsValueMap SignalDef
 
+useMapToDefMap :: SignalUseMap -> SignalDefMap
+useMapToDefMap (Single (SignalUse u)) = Single (SignalDef u)
+useMapToDefMap (Tuple uses) = Tuple (map useMapToDefMap uses)
+
+type SignalId = Int
 data SignalUse = SignalUse {
-  sigUseId :: Int
+  sigUseId :: SignalId
 } deriving (Show, Eq)
 
 data SignalDef = SignalDef {
-  sigDefId :: Int
+  sigDefId :: SignalId
 } deriving (Show, Eq)
 
-data App = App {
+data FApp = FApp {
   appFunc :: HsFunction,
   appArgs :: [SignalUseMap],
   appRes  :: SignalDefMap
@@ -66,16 +105,57 @@ data HsFunction = HsFunction {
 } deriving (Show, Eq)
 
 type BindMap = [(
-  String,              -- ^ The bind name
+  CoreBndr,            -- ^ The bind name
   Either               -- ^ The bind value which is either
-    SignalUse          -- ^ a signal
+    SignalUseMap       -- ^ a signal
     (
       HsValueUse,      -- ^ or a HighOrder function
       [SignalUse]      -- ^ With these signals already applied to it
     )
   )]
 
-type FlattenState = State.State ([App], [CondDef], Int)
+type FlattenState = State.State ([FApp], [CondDef], SignalId)
+
+-- | Add an application to the current FlattenState
+addApp :: FApp -> FlattenState ()
+addApp a = do
+  (apps, conds, n) <- State.get
+  State.put (a:apps, conds, n)
+
+-- | Add a conditional definition to the current FlattenState
+addCondDef :: CondDef -> FlattenState ()
+addCondDef c = do
+  (apps, conds, n) <- State.get
+  State.put (apps, c:conds, n)
+
+-- | Generates a new signal id, which is unique within the current flattening.
+genSignalId :: FlattenState SignalId 
+genSignalId = do
+  (apps, conds, n) <- State.get
+  State.put (apps, conds, n+1)
+  return n
+
+genSignalUses ::
+  Type.Type
+  -> FlattenState SignalUseMap
+
+genSignalUses ty = do
+  typeMapToUseMap tymap
+  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 <- mapM typeMapToUseMap tymaps
+  return $ Tuple usemaps
 
 -- | Flatten a haskell function
 flattenFunction ::
@@ -88,18 +168,52 @@ flattenFunction hsfunc bind@(NonRec var expr) =
   FlatFunction args res apps conds
   where
     init_state        = ([], [], 0)
-    (fres, end_state) = State.runState (flattenExpr expr) init_state
+    (fres, end_state) = State.runState (flattenExpr [] expr) init_state
     (args, res)       = fres
     (apps, conds, _)  = end_state
 
 flattenExpr ::
-  CoreExpr
+  BindMap
+  -> CoreExpr
   -> FlattenState ([SignalDefMap], SignalUseMap)
 
-flattenExpr _ = do
-  return ([], Tuple [])
-
+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
+  let binds' = (b, Left defs):binds
+  (args, res) <- flattenExpr binds' expr
+  return ((useMapToDefMap defs) : args, res)
+
+flattenExpr binds (Var id) =
+  case bind of
+    Left sig_use -> return ([], sig_use)
+    Right _ -> error "Higher order functions not supported."
+  where
+    bind = Maybe.fromMaybe
+      (error $ "Argument " ++ Name.getOccString id ++ "is unknown")
+      (lookup id binds)
+
+flattenExpr binds app@(App _ _) = do
+  -- Is this a data constructor application?
+  case CoreUtils.exprIsConApp_maybe app of
+    -- Is this a tuple construction?
+    Just (dc, args) -> if DataCon.isTupleCon dc 
+      then
+        flattenBuildTupleExpr binds (dataConAppArgs dc args)
+      else
+        error $ "Data constructors other than tuples not supported: " ++ (showSDoc $ ppr app)
+    otherwise ->
+      -- Normal function application
+      let ((Var f), args) = collectArgs app in
+      flattenApplicationExpr binds (CoreUtils.exprType app) f args
+  where
+    flattenBuildTupleExpr = error $ "Tuple construction not supported: " ++ (showSDoc $ ppr app)
+    flattenApplicationExpr binds ty f args = error $ "Function application not supported: " ++ (showSDoc $ ppr app)
 
+flattenExpr _ _ = do
+  return ([], Tuple [])
 
 
 -- vim: set ts=8 sw=2 sts=2 expandtab: