Merge branch 'cλash' of http://git.stderr.nl/matthijs/projects/master-project
[matthijs/master-project/cλash.git] / Generate.hs
index 5c1ca08ba7fd2f4137b42c44ce5d675dced638cc..8065363ca53b8ec7965e1636f4f6ba16e6907532 100644 (file)
@@ -1,65 +1,93 @@
 module Generate where
 
+-- Standard modules
 import qualified Control.Monad as Monad
 import qualified Maybe
 
+-- ForSyDe
 import qualified ForSyDe.Backend.VHDL.AST as AST
+
+-- GHC API
+import CoreSyn
+import qualified Var
+
+-- Local imports
 import Constants
 import VHDLTypes
+import VHDLTools
+import CoreTools
 
 -- | Generate a binary operator application. The first argument should be a
 -- constructor from the AST.Expr type, e.g. AST.And.
-genExprOp2 :: (AST.Expr -> AST.Expr -> AST.Expr) -> [AST.Expr] -> AST.Expr
-genExprOp2 op [arg1, arg2] = op arg1 arg2
+genExprOp2 :: (AST.Expr -> AST.Expr -> AST.Expr) -> [AST.Expr] -> VHDLSession AST.Expr
+genExprOp2 op [arg1, arg2] = return $ op arg1 arg2
 
 -- | Generate a unary operator application
-genExprOp1 :: (AST.Expr -> AST.Expr) -> [AST.Expr] -> AST.Expr
-genExprOp1 op [arg] = op arg
+genExprOp1 :: (AST.Expr -> AST.Expr) -> [AST.Expr] -> VHDLSession AST.Expr
+genExprOp1 op [arg] = return $ op arg
 
 -- | Generate a function call from the Function Name and a list of expressions
 --   (its arguments)
-genExprFCall :: AST.VHDLId -> [AST.Expr] -> AST.Expr
+genExprFCall :: AST.VHDLId -> [AST.Expr] -> VHDLSession AST.Expr
 genExprFCall fName args = 
-   AST.PrimFCall $ AST.FCall (AST.NSimple fName)  $
+   return $ AST.PrimFCall $ AST.FCall (AST.NSimple fName)  $
              map (\exp -> Nothing AST.:=>: AST.ADExpr exp) args
 
 -- | Generate a generate statement for the builtin function "map"
 genMapCall :: 
-  Int -- | The length of the vector 
-  -> Entity -- | The entity to map
-  -> [AST.VHDLId] -- | The vectors
-  -> AST.GenerateSm -- | The resulting generate statement
-genMapCall len entity [arg, res] = genSm
+  Entity -- | The entity to map
+  -> [CoreSyn.CoreBndr] -- | The vectors
+  -> VHDLSession AST.GenerateSm -- | The resulting generate statement
+genMapCall entity [arg, res] = return $ genSm
+  where
+    -- Setup the generate scheme
+    len         = (tfvec_len . Var.varType) res
+    label       = mkVHDLExtId ("mapVector" ++ (varToString res))
+    nPar        = AST.unsafeVHDLBasicId "n"
+    range       = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
+    genScheme   = AST.ForGn nPar range
+    -- Get the entity name and port names
+    entity_id   = ent_id entity
+    argports   = map (Monad.liftM fst) (ent_args entity)
+    resport     = (Monad.liftM fst) (ent_res entity)
+    -- Assign the ports
+    inport      = mkAssocElemIndexed (argports!!0) (varToString arg) nPar
+    outport     = mkAssocElemIndexed resport (varToString res) nPar
+    clk_port    = mkAssocElem (Just $ mkVHDLExtId "clk") "clk"
+    portassigns = Maybe.catMaybes [inport,outport,clk_port]
+    -- Generate the portmap
+    mapLabel    = "map" ++ (AST.fromVHDLId entity_id)
+    compins     = mkComponentInst mapLabel entity_id portassigns
+    -- Return the generate functions
+    genSm       = AST.GenerateSm label genScheme [] [compins]
+    
+genZipWithCall ::
+  Entity
+  -> [CoreSyn.CoreBndr]
+  -> AST.GenerateSm
+genZipWithCall entity [arg1, arg2, res] = genSm
   where
-    label = mkVHDLExtId ("mapVector" ++ (AST.fromVHDLId res))
-    nPar  = AST.unsafeVHDLBasicId "n"
-    range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
-    genScheme = AST.ForGn nPar range
-    entity_id = ent_id entity
-    argport = map (Monad.liftM fst) (ent_args entity)
-    resport = (Monad.liftM fst) (ent_res entity)
-    inport = mkAssocElemI (head argport) arg
-    outport = mkAssocElemI resport res
-    clk_port = mkAssocElem (Just $ mkVHDLExtId "clk") "clk"
-    portmaps = Maybe.catMaybes [inport,outport,clk_port]
-    portname = mkVHDLExtId ("map" ++ (AST.fromVHDLId entity_id))
-    portmap = AST.CSISm $ AST.CompInsSm (AST.unsafeVHDLBasicId "map12") (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
-    genSm = AST.GenerateSm label genScheme [] [portmap]
-    -- | Create an VHDL port -> signal association
-    mkAssocElemI :: Maybe AST.VHDLId -> AST.VHDLId -> Maybe AST.AssocElem
-    mkAssocElemI (Just port) signal = Just $ Just port AST.:=>: (AST.ADName (AST.NIndexed (AST.IndexedName 
-                    (AST.NSimple signal) [AST.PrimName $ AST.NSimple nPar])))
-    mkAssocElemI Nothing _ = Nothing
-    mkAssocElem :: Maybe AST.VHDLId -> String -> Maybe AST.AssocElem
-    mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADName (AST.NSimple (mkVHDLExtId signal))) 
-    mkAssocElem Nothing _ = Nothing
-    mkVHDLExtId :: String -> AST.VHDLId
-    mkVHDLExtId s = 
-      AST.unsafeVHDLExtId $ strip_invalid s
-      where 
-        -- Allowed characters, taken from ForSyde's mkVHDLExtId
-        allowed = ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ " \"#&\\'()*+,./:;<=>_|!$%@?[]^`{}~-"
-        strip_invalid = filter (`elem` allowed)
+    -- Setup the generate scheme
+    len         = (tfvec_len . Var.varType) res
+    label       = mkVHDLExtId ("zipWithVector" ++ (varToString res))
+    nPar        = AST.unsafeVHDLBasicId "n"
+    range       = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
+    genScheme   = AST.ForGn nPar range
+    -- Get the entity name and port names
+    entity_id   = ent_id entity
+    argports    = map (Monad.liftM fst) (ent_args entity)
+    resport     = (Monad.liftM fst) (ent_res entity)
+    -- Assign the ports
+    inport1     = mkAssocElemIndexed (argports!!0) (varToString arg1) nPar
+    inport2     = mkAssocElemIndexed (argports!!1) (varToString arg2) nPar 
+    outport     = mkAssocElemIndexed resport (varToString res) nPar
+    clk_port    = mkAssocElem (Just $ mkVHDLExtId "clk") "clk"
+    portassigns = Maybe.catMaybes [inport1,inport2,outport,clk_port]
+    -- Generate the portmap
+    mapLabel    = "zipWith" ++ (AST.fromVHDLId entity_id)
+    compins     = mkComponentInst mapLabel entity_id portassigns
+    -- Return the generate functions
+    genSm       = AST.GenerateSm label genScheme [] [compins]
 
 genUnconsVectorFuns :: AST.TypeMark -- ^ type of the vector elements
                     -> AST.TypeMark -- ^ type of the vector
@@ -74,7 +102,7 @@ genUnconsVectorFuns elemTM vectorTM  =
   , AST.SubProgBody takeSpec    [AST.SPVD takeVar]  [takeExpr, takeRet]         
   , AST.SubProgBody dropSpec    [AST.SPVD dropVar]  [dropExpr, dropRet]    
   , AST.SubProgBody plusgtSpec  [AST.SPVD plusgtVar] [plusgtExpr, plusgtRet]
-  , AST.SubProgBody emptySpec   [AST.SPVD emptyVar] [emptyExpr]
+  , AST.SubProgBody emptySpec   [AST.SPCD emptyVar] [emptyExpr]
   , AST.SubProgBody singletonSpec [AST.SPVD singletonVar] [singletonRet] 
   , AST.SubProgBody copySpec    [AST.SPVD copyVar]      [copyExpr]
   ]
@@ -217,12 +245,9 @@ genUnconsVectorFuns elemTM vectorTM  =
     plusgtRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
     emptySpec = AST.Function emptyId [] vectorTM
     emptyVar = 
-          AST.VarDec resId 
-              (AST.SubtypeIn vectorTM
-                (Just $ AST.ConstraintIndex $ AST.IndexConstraint 
-                 [AST.ToRange (AST.PrimLit "0")
-                          (AST.PrimLit "-1")]))
-              Nothing
+          AST.ConstDec resId 
+              (AST.SubtypeIn vectorTM Nothing)
+              (Just $ AST.PrimLit "\"\"")
     emptyExpr = AST.ReturnSm (Just $ AST.PrimName (AST.NSimple resId))
     singletonSpec = AST.Function singletonId [AST.IfaceVarDec aPar elemTM ] 
                                          vectorTM
@@ -248,4 +273,4 @@ genUnconsVectorFuns elemTM vectorTM  =
              (Just $ AST.Aggregate [AST.ElemAssoc (Just AST.Others) 
                                           (AST.PrimName $ AST.NSimple aPar)])
     -- return res
-    copyExpr = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
\ No newline at end of file
+    copyExpr = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)