Merge branch 'cλash' of http://git.stderr.nl/matthijs/projects/master-project
[matthijs/master-project/cλash.git] / Generate.hs
index f55aa3d9e5e029312cb19a1de239d3e226497b98..e6a5d45503c6879b1b4df8e6136754074f92d9c9 100644 (file)
@@ -84,9 +84,11 @@ genFCall' (Right name) _ _ = error $ "Cannot generate builtin function call assi
 
 -- | Generate a generate statement for the builtin function "map"
 genMap :: BuiltinBuilder
-genMap = genVarArgs genMap'
-genMap' :: (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
-genMap' (Left res) f [mapped_f, arg] =
+genMap (Left res) f [Left mapped_f, Left (Var arg)] =
+  -- mapped_f must be a CoreExpr (since we can't represent functions as VHDL
+  -- expressions). arg must be a CoreExpr (and should be a CoreSyn.Var), since
+  -- we must index it (which we couldn't if it was a VHDL Expr, since only
+  -- VHDLNames can be indexed).
   let
     -- Setup the generate scheme
     len         = (tfvec_len . Var.varType) res
@@ -102,7 +104,9 @@ genMap' (Left res) f [mapped_f, arg] =
     resname     = mkIndexedName (varToVHDLName res) n_expr
     argexpr     = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg) n_expr
   in do
-    app_concsms <- genApplication (Right resname) mapped_f [Right argexpr]
+    let (CoreSyn.Var real_f, already_mapped_args) = CoreSyn.collectArgs mapped_f
+    let valargs = get_val_args (Var.varType real_f) already_mapped_args
+    app_concsms <- genApplication (Right resname) real_f (map Left valargs ++ [Right argexpr])
     -- Return the generate statement
     return [AST.CSGSm $ AST.GenerateSm label genScheme [] app_concsms]
 
@@ -222,6 +226,60 @@ genFold' left (Left res) f [folded_f, start, vec] = do
       -- Return the conditional generate part
       return $ AST.GenerateSm cond_label cond_scheme [] app_concsms
 
+-- | Generate a generate statement for the builtin function "zip"
+genZip :: BuiltinBuilder
+genZip = genVarArgs genZip'
+genZip' :: (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
+genZip' (Left res) f args@[arg1, arg2] =
+  let
+    -- Setup the generate scheme
+    len             = (tfvec_len . Var.varType) res
+    -- TODO: Use something better than varToString
+    label           = mkVHDLExtId ("zipVector" ++ (varToString res))
+    n_id            = mkVHDLBasicId "n"
+    n_expr          = idToVHDLExpr n_id
+    range           = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
+    genScheme       = AST.ForGn n_id range
+    resname'        = mkIndexedName (varToVHDLName res) n_expr
+    argexpr1        = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg1) n_expr
+    argexpr2        = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg2) n_expr
+  in do
+    labels <- getFieldLabels (tfvec_elem (Var.varType res))
+    let resnameA    = mkSelectedName resname' (labels!!0)
+    let resnameB    = mkSelectedName resname' (labels!!1)
+    let resA_assign = mkUncondAssign (Right resnameA) argexpr1
+    let resB_assign = mkUncondAssign (Right resnameB) argexpr2
+    -- Return the generate functions
+    return [AST.CSGSm $ AST.GenerateSm label genScheme [] [resA_assign,resB_assign]]
+    
+-- | Generate a generate statement for the builtin function "unzip"
+genUnzip :: BuiltinBuilder
+genUnzip = genVarArgs genUnzip'
+genUnzip' :: (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
+genUnzip' (Left res) f args@[arg] =
+  let
+    -- Setup the generate scheme
+    len             = (tfvec_len . Var.varType) arg
+    -- TODO: Use something better than varToString
+    label           = mkVHDLExtId ("unzipVector" ++ (varToString res))
+    n_id            = mkVHDLBasicId "n"
+    n_expr          = idToVHDLExpr n_id
+    range           = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
+    genScheme       = AST.ForGn n_id range
+    resname'        = varToVHDLName res
+    argexpr'        = mkIndexedName (varToVHDLName arg) n_expr
+  in do
+    reslabels <- getFieldLabels (Var.varType res)
+    arglabels <- getFieldLabels (tfvec_elem (Var.varType arg))
+    let resnameA    = mkIndexedName (mkSelectedName resname' (reslabels!!0)) n_expr
+    let resnameB    = mkIndexedName (mkSelectedName resname' (reslabels!!1)) n_expr
+    let argexprA    = vhdlNameToVHDLExpr $ mkSelectedName argexpr' (arglabels!!0)
+    let argexprB    = vhdlNameToVHDLExpr $ mkSelectedName argexpr' (arglabels!!1)
+    let resA_assign = mkUncondAssign (Right resnameA) argexprA
+    let resB_assign = mkUncondAssign (Right resnameB) argexprB
+    -- Return the generate functions
+    return [AST.CSGSm $ AST.GenerateSm label genScheme [] [resA_assign,resB_assign]]
+
 -----------------------------------------------------------------------------
 -- Function to generate VHDL for applications
 -----------------------------------------------------------------------------
@@ -318,10 +376,15 @@ genUnconsVectorFuns elemTM vectorTM  =
   , (singletonId, AST.SubProgBody singletonSpec [AST.SPVD singletonVar] [singletonRet])
   , (copyId, AST.SubProgBody copySpec    [AST.SPVD copyVar]      [copyExpr])
   , (selId, AST.SubProgBody selSpec  [AST.SPVD selVar] [selFor, selRet])
+  , (ltplusId, AST.SubProgBody ltplusSpec [AST.SPVD ltplusVar] [ltplusExpr, ltplusRet]  )  
+  , (plusplusId, AST.SubProgBody plusplusSpec [AST.SPVD plusplusVar] [plusplusExpr, plusplusRet])
+  , (lengthTId, AST.SubProgBody lengthTSpec [] [lengthTExpr])
   ]
   where 
     ixPar   = AST.unsafeVHDLBasicId "ix"
     vecPar  = AST.unsafeVHDLBasicId "vec"
+    vec1Par = AST.unsafeVHDLBasicId "vec1"
+    vec2Par = AST.unsafeVHDLBasicId "vec2"
     nPar    = AST.unsafeVHDLBasicId "n"
     iId     = AST.unsafeVHDLBasicId "i"
     iPar    = iId
@@ -490,8 +553,8 @@ genUnconsVectorFuns elemTM vectorTM  =
     -- return res
     copyExpr = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
     selSpec = AST.Function (mkVHDLExtId selId) [AST.IfaceVarDec fPar   naturalTM,
-                               AST.IfaceVarDec nPar   naturalTM,
                                AST.IfaceVarDec sPar   naturalTM,
+                               AST.IfaceVarDec nPar   naturalTM,
                                AST.IfaceVarDec vecPar vectorTM ] vectorTM
     -- variable res : fsvec_x (0 to n-1);
     selVar = 
@@ -515,6 +578,43 @@ genUnconsVectorFuns elemTM vectorTM  =
                                     (AST.PrimName $ AST.NIndexed (AST.IndexedName (AST.NSimple vecPar) [origExp]))
     -- return res;
     selRet =  AST.ReturnSm (Just $ AST.PrimName (AST.NSimple resId))
+    ltplusSpec = AST.Function (mkVHDLExtId ltplusId) [AST.IfaceVarDec vecPar vectorTM,
+                                        AST.IfaceVarDec aPar   elemTM] vectorTM 
+     -- variable res : fsvec_x (0 to vec'length);
+    ltplusVar = 
+      AST.VarDec resId 
+        (AST.SubtypeIn vectorTM
+          (Just $ AST.ConstraintIndex $ AST.IndexConstraint 
+            [AST.ToRange (AST.PrimLit "0")
+              (AST.PrimName (AST.NAttribute $ 
+                AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing))]))
+        Nothing
+    ltplusExpr = AST.NSimple resId AST.:= 
+                     ((AST.PrimName $ AST.NSimple vecPar) AST.:&: 
+                      (AST.PrimName $ AST.NSimple aPar))
+    ltplusRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
+    plusplusSpec = AST.Function (mkVHDLExtId plusplusId) [AST.IfaceVarDec vec1Par vectorTM,
+                                             AST.IfaceVarDec vec2Par vectorTM] 
+                                             vectorTM 
+    -- variable res : fsvec_x (0 to vec1'length + vec2'length -1);
+    plusplusVar = 
+      AST.VarDec resId 
+        (AST.SubtypeIn vectorTM
+          (Just $ AST.ConstraintIndex $ AST.IndexConstraint 
+            [AST.ToRange (AST.PrimLit "0")
+              (AST.PrimName (AST.NAttribute $ 
+                AST.AttribName (AST.NSimple vec1Par) (mkVHDLBasicId lengthId) Nothing) AST.:+:
+                  AST.PrimName (AST.NAttribute $ 
+                AST.AttribName (AST.NSimple vec2Par) (mkVHDLBasicId lengthId) Nothing) AST.:-:
+                  AST.PrimLit "1")]))
+       Nothing
+    plusplusExpr = AST.NSimple resId AST.:= 
+                     ((AST.PrimName $ AST.NSimple vec1Par) AST.:&: 
+                      (AST.PrimName $ AST.NSimple vec2Par))
+    plusplusRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
+    lengthTSpec = AST.Function (mkVHDLExtId lengthTId) [AST.IfaceVarDec vecPar vectorTM] naturalTM
+    lengthTExpr = AST.ReturnSm (Just $ AST.PrimName (AST.NAttribute $ 
+                                AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing))
 
 -----------------------------------------------------------------------------
 -- A table of builtin functions
@@ -534,13 +634,18 @@ globalNameTable = Map.fromList
   , (dropId           , (2, genFCall                ) )
   , (selId            , (4, genFCall                ) )
   , (plusgtId         , (2, genFCall                ) )
+  , (ltplusId         , (2, genFCall                ) )
+  , (plusplusId       , (2, genFCall                ) )
   , (mapId            , (2, genMap                  ) )
   , (zipWithId        , (3, genZipWith              ) )
   , (foldlId          , (3, genFoldl                ) )
   , (foldrId          , (3, genFoldr                ) )
+  , (zipId            , (2, genZip                  ) )
+  , (unzipId          , (1, genUnzip                ) )
   , (emptyId          , (0, genFCall                ) )
   , (singletonId      , (1, genFCall                ) )
   , (copyId           , (2, genFCall                ) )
+  , (lengthTId        , (1, genFCall                ) )
   , (hwxorId          , (2, genOperator2 AST.Xor    ) )
   , (hwandId          , (2, genOperator2 AST.And    ) )
   , (hworId           , (2, genOperator2 AST.Or     ) )