Merge branch 'cλash' of http://git.stderr.nl/matthijs/projects/master-project
[matthijs/master-project/cλash.git] / Generate.hs
index 5be869459ff445576861811d7cec822ba24d70d6..e6a5d45503c6879b1b4df8e6136754074f92d9c9 100644 (file)
@@ -84,158 +84,202 @@ 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' (Left res) f [mapped_f, arg] = do
-  signatures <- getA vsSignatures
-  let entity = Maybe.fromMaybe
-        (error $ "Using function '" ++ (varToString mapped_f) ++ "' without signature? This should not happen!") 
-        (Map.lookup mapped_f signatures)
+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
     -- TODO: Use something better than varToString
     label       = mkVHDLExtId ("mapVector" ++ (varToString res))
-    nPar        = AST.unsafeVHDLBasicId "n"
+    n_id        = mkVHDLBasicId "n"
+    n_expr      = idToVHDLExpr n_id
     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) (varToVHDLId arg) nPar
-    outport     = mkAssocElemIndexed resport (varToVHDLId res) nPar
-    portassigns = Maybe.catMaybes [inport,outport]
-    -- Generate the portmap
-    mapLabel    = "map" ++ (AST.fromVHDLId entity_id)
-    compins     = mkComponentInst mapLabel entity_id portassigns
-    -- Return the generate functions
-    genSm       = AST.CSGSm $ AST.GenerateSm label genScheme [] [compins]
-    in
-      return $ [genSm]
+    genScheme   = AST.ForGn n_id range
+
+    -- Create the content of the generate statement: Applying the mapped_f to
+    -- each of the elements in arg, storing to each element in res
+    resname     = mkIndexedName (varToVHDLName res) n_expr
+    argexpr     = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg) n_expr
+  in do
+    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]
+
 genMap' (Right name) _ _ = error $ "Cannot generate map function call assigned to a VHDLName: " ++ show name
     
 genZipWith :: BuiltinBuilder
 genZipWith = genVarArgs genZipWith'
 genZipWith' :: (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
-genZipWith' (Left res) f args@[zipped_f, arg1, arg2] = do
-  signatures <- getA vsSignatures
-  let entity = Maybe.fromMaybe
-        (error $ "Using function '" ++ (varToString zipped_f) ++ "' without signature? This should not happen!") 
-        (Map.lookup zipped_f signatures)
+genZipWith' (Left res) f args@[zipped_f, arg1, arg2] =
   let
     -- Setup the generate scheme
     len         = (tfvec_len . Var.varType) res
     -- TODO: Use something better than varToString
     label       = mkVHDLExtId ("zipWithVector" ++ (varToString res))
-    nPar        = AST.unsafeVHDLBasicId "n"
+    n_id        = mkVHDLBasicId "n"
+    n_expr      = idToVHDLExpr n_id
     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) (varToVHDLId arg1) nPar
-    inport2     = mkAssocElemIndexed (argports!!1) (varToVHDLId arg2) nPar 
-    outport     = mkAssocElemIndexed resport (varToVHDLId res) nPar
-    portassigns = Maybe.catMaybes [inport1,inport2,outport]
-    -- Generate the portmap
-    mapLabel    = "zipWith" ++ (AST.fromVHDLId entity_id)
-    compins     = mkComponentInst mapLabel entity_id portassigns
+    genScheme   = AST.ForGn n_id range
+
+    -- Create the content of the generate statement: Applying the zipped_f to
+    -- each of the elements in arg1 and arg2, storing to each element in res
+    resname     = mkIndexedName (varToVHDLName res) n_expr
+    argexpr1    = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg1) n_expr
+    argexpr2    = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg2) n_expr
+  in do
+    app_concsms <- genApplication (Right resname) zipped_f [Right argexpr1, Right argexpr2]
     -- Return the generate functions
-    genSm       = AST.CSGSm $ AST.GenerateSm label genScheme [] [compins]
-    in
-      return $ [genSm]
-{-
+    return [AST.CSGSm $ AST.GenerateSm label genScheme [] app_concsms]
+
 genFoldl :: BuiltinBuilder
-genFoldl = genVarArgs genFoldl'
-genFoldl' resVal f [folded_f, startVal, inVec] = do
-  signatures <- getA vsSignatures
-  let entity = Maybe.fromMaybe
-        (error $ "Using function '" ++ (varToString folded_f) ++ "' without signature? This should not happen!") 
-        (Map.lookup folded_f signatures)
-  let (vec, _) = splitAppTy (Var.varType inVec)
-  let vecty = Type.mkAppTy vec (Var.varType startVal)
-  vecType <- vhdl_ty vecty
+genFoldl = genFold True
+
+genFoldr :: BuiltinBuilder
+genFoldr = genFold False
+
+genFold :: Bool -> BuiltinBuilder
+genFold left = genVarArgs (genFold' left)
+genFold' :: Bool -> (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
+-- Special case for an empty input vector, just assign start to res
+genFold' left (Left res) _ [_, start, vec] | len == 0 = return [mkUncondAssign (Left res) (varToVHDLExpr start)]
+    where len = (tfvec_len . Var.varType) vec
+genFold' left (Left res) f [folded_f, start, vec] = do
+  -- evec is (TFVec n), so it still needs an element type
+  let (nvec, _) = splitAppTy (Var.varType vec)
+  -- Put the type of the start value in nvec, this will be the type of our
+  -- temporary vector
+  let tmp_ty = Type.mkAppTy nvec (Var.varType start)
+  tmp_vhdl_ty <- vhdl_ty tmp_ty
   -- Setup the generate scheme
-  let  len         = (tfvec_len . Var.varType) inVec
-  let  genlabel       = mkVHDLExtId ("foldlVector" ++ (varToString inVec))
-  let  blockLabel  = mkVHDLExtId ("foldlVector" ++ (varToString startVal))
-  let  range       = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
-  let  genScheme   = AST.ForGn (AST.unsafeVHDLBasicId "n") range
+  let gen_label = mkVHDLExtId ("foldlVector" ++ (varToString vec))
+  let block_label = mkVHDLExtId ("foldlVector" ++ (varToString start))
+  let gen_range = if left then AST.ToRange (AST.PrimLit "0") len_min_expr
+                  else AST.DownRange len_min_expr (AST.PrimLit "0")
+  let gen_scheme   = AST.ForGn n_id gen_range
   -- Make the intermediate vector
-  let  tmpVec      = AST.BDISD $ AST.SigDec (mkVHDLExtId "tmp") vecType Nothing
-  -- Get the entity name and port names
-  let entity_id   = ent_id entity
-  let argports    = map (Monad.liftM fst) (ent_args entity)
-  let resport     = (Monad.liftM fst) (ent_res entity)
-  -- Return the generate functions
-  let genSm       = AST.GenerateSm genlabel genScheme [] 
-                      [ AST.CSGSm (genFirstCell (entity_id, argports, resport) 
-                                    [startVal, inVec, resVal])
-                      , AST.CSGSm (genOtherCell (entity_id, argports, resport) 
-                                    [startVal, inVec, resVal])
-                      , AST.CSGSm (genLastCell (entity_id, argports, resport) 
-                                    [startVal, inVec, resVal])
-                      ]
-  return $ [AST.CSBSm $ AST.BlockSm blockLabel [] (AST.PMapAspect []) [tmpVec] [AST.CSGSm genSm]]
+  let  tmp_dec     = AST.BDISD $ AST.SigDec tmp_id tmp_vhdl_ty Nothing
+  -- Create the generate statement
+  cells <- sequence [genFirstCell, genOtherCell]
+  let gen_sm = AST.GenerateSm gen_label gen_scheme [] (map AST.CSGSm cells)
+  -- Assign tmp[len-1] or tmp[0] to res
+  let out_assign = mkUncondAssign (Left res) $ vhdlNameToVHDLExpr (if left then
+                    (mkIndexedName tmp_name (AST.PrimLit $ show (len-1))) else
+                    (mkIndexedName tmp_name (AST.PrimLit "0")))      
+  let block = AST.BlockSm block_label [] (AST.PMapAspect []) [tmp_dec] [AST.CSGSm gen_sm, out_assign]
+  return [AST.CSBSm block]
   where
-    genFirstCell (entity_id, argports, resport) [startVal, inVec, resVal] = cellGn
-      where
-        cellLabel    = mkVHDLExtId "firstcell"
-        cellGenScheme = AST.IfGn ((AST.PrimName $ AST.NSimple nPar)  AST.:=: (AST.PrimLit "0"))
-        tmpId       = mkVHDLExtId "tmp"
-        nPar        = AST.unsafeVHDLBasicId "n"
-        -- Assign the ports
-        inport1     = mkAssocElem (argports!!0) (varToString startVal)
-        inport2     = mkAssocElemIndexed (argports!!1) (varToVHDLId inVec) nPar 
-        outport     = mkAssocElemIndexed resport tmpId nPar
-        portassigns = Maybe.catMaybes [inport1,inport2,outport]
-        -- Generate the portmap
-        mapLabel    = "cell" ++ (AST.fromVHDLId entity_id)
-        compins     = mkComponentInst mapLabel entity_id portassigns
-        -- Return the generate functions
-        cellGn       = AST.GenerateSm cellLabel cellGenScheme [] [compins]
-    genOtherCell (entity_id, argports, resport) [startVal, inVec, resVal] = cellGn
-      where
-        len         = (tfvec_len . Var.varType) inVec
-        cellLabel    = mkVHDLExtId "othercell"
-        cellGenScheme = AST.IfGn $ AST.And ((AST.PrimName $ AST.NSimple nPar)  AST.:>: (AST.PrimLit "0"))
-                                ((AST.PrimName $ AST.NSimple nPar)  AST.:<: (AST.PrimLit $ show (len-1)))
-        tmpId       = mkVHDLExtId "tmp"
-        nPar        = AST.unsafeVHDLBasicId "n"
-        -- Assign the ports
-        inport1     = mkAssocElemIndexed (argports!!0) tmpId (AST.unsafeVHDLBasicId "n-1")
-        inport2     = mkAssocElemIndexed (argports!!1) (varToVHDLId inVec) nPar 
-        outport     = mkAssocElemIndexed resport tmpId nPar
-        portassigns = Maybe.catMaybes [inport1,inport2,outport]
-        -- Generate the portmap
-        mapLabel    = "cell" ++ (AST.fromVHDLId entity_id)
-        compins     = mkComponentInst mapLabel entity_id portassigns
-        -- Return the generate functions
-        cellGn      = AST.GenerateSm cellLabel cellGenScheme [] [compins]
-    genLastCell (entity_id, argports, resport) [startVal, inVec, resVal] = cellGn
-      where
-        len         = (tfvec_len . Var.varType) inVec
-        cellLabel    = mkVHDLExtId "lastCell"
-        cellGenScheme = AST.IfGn ((AST.PrimName $ AST.NSimple nPar)  AST.:=: (AST.PrimLit $ show (len-1)))
-        tmpId       = mkVHDLExtId "tmp"
-        nPar        = AST.unsafeVHDLBasicId "n"
-        -- Assign the ports
-        inport1     = mkAssocElemIndexed (argports!!0) tmpId (AST.unsafeVHDLBasicId "n-1")
-        inport2     = mkAssocElemIndexed (argports!!1) (varToVHDLId inVec) nPar 
-        outport     = mkAssocElemIndexed resport tmpId nPar
-        portassigns = Maybe.catMaybes [inport1,inport2,outport]
-        -- Generate the portmap
-        mapLabel    = "cell" ++ (AST.fromVHDLId entity_id)
-        compins     = mkComponentInst mapLabel entity_id portassigns
-        -- Generate the output assignment
-        assign      = mkUncondAssign (Left resVal) (AST.PrimName (AST.NIndexed (AST.IndexedName 
-                              (AST.NSimple tmpId) [AST.PrimLit $ show (len-1)])))
-        -- Return the generate functions
-        cellGn      = AST.GenerateSm cellLabel cellGenScheme [] [compins,assign]
--}
+    -- The vector length
+    len         = (tfvec_len . Var.varType) vec
+    -- An id for the counter
+    n_id = mkVHDLBasicId "n"
+    n_cur = idToVHDLExpr n_id
+    -- An expression for previous n
+    n_prev = if left then (n_cur AST.:-: (AST.PrimLit "1"))
+                     else (n_cur AST.:+: (AST.PrimLit "1"))
+    -- An expression for len-1
+    len_min_expr = (AST.PrimLit $ show (len-1))
+    -- An id for the tmp result vector
+    tmp_id = mkVHDLBasicId "tmp"
+    tmp_name = AST.NSimple tmp_id
+    -- Generate parts of the fold
+    genFirstCell, genOtherCell :: VHDLSession AST.GenerateSm
+    genFirstCell = do
+      let cond_label = mkVHDLExtId "firstcell"
+      -- if n == 0 or n == len-1
+      let cond_scheme = AST.IfGn $ n_cur AST.:=: (if left then (AST.PrimLit "0")
+                                                  else (AST.PrimLit $ show (len-1)))
+      -- Output to tmp[current n]
+      let resname = mkIndexedName tmp_name n_cur
+      -- Input from start
+      let argexpr1 = varToVHDLExpr start
+      -- Input from vec[current n]
+      let argexpr2 = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName vec) n_cur
+      app_concsms <- genApplication (Right resname) folded_f  ( if left then
+                                                                  [Right argexpr1, Right argexpr2]
+                                                                else
+                                                                  [Right argexpr2, Right argexpr1]
+                                                              )
+      -- Return the conditional generate part
+      return $ AST.GenerateSm cond_label cond_scheme [] app_concsms
+
+    genOtherCell = do
+      let cond_label = mkVHDLExtId "othercell"
+      -- if n > 0 or n < len-1
+      let cond_scheme = AST.IfGn $ n_cur AST.:/=: (if left then (AST.PrimLit "0")
+                                                   else (AST.PrimLit $ show (len-1)))
+      -- Output to tmp[current n]
+      let resname = mkIndexedName tmp_name n_cur
+      -- Input from tmp[previous n]
+      let argexpr1 = vhdlNameToVHDLExpr $ mkIndexedName tmp_name n_prev
+      -- Input from vec[current n]
+      let argexpr2 = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName vec) n_cur
+      app_concsms <- genApplication (Right resname) folded_f  ( if left then
+                                                                  [Right argexpr1, Right argexpr2]
+                                                                else
+                                                                  [Right argexpr2, Right argexpr1]
+                                                              )
+      -- 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
 -----------------------------------------------------------------------------
@@ -282,7 +326,7 @@ genApplication dst f args =
         entity_id = ent_id signature
         -- TODO: Using show here isn't really pretty, but we'll need some
         -- unique-ish value...
-        label = "comp_ins_" ++ (either show show) dst
+        label = "comp_ins_" ++ (either show prettyShow) dst
         portmaps = mkAssocElems (map (either exprToVHDLExpr id) args) ((either varToVHDLName id) dst) signature
         in
           return [mkComponentInst label entity_id portmaps]
@@ -331,14 +375,22 @@ genUnconsVectorFuns elemTM vectorTM  =
   , (emptyId, AST.SubProgBody emptySpec   [AST.SPCD emptyVar] [emptyExpr])
   , (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
     aPar    = AST.unsafeVHDLBasicId "a"
+    fPar = AST.unsafeVHDLBasicId "f"
+    sPar = AST.unsafeVHDLBasicId "s"
     resId   = AST.unsafeVHDLBasicId "res"
     exSpec = AST.Function (mkVHDLExtId exId) [AST.IfaceVarDec vecPar vectorTM,
                                AST.IfaceVarDec ixPar  naturalTM] elemTM
@@ -500,6 +552,69 @@ genUnconsVectorFuns elemTM vectorTM  =
                                           (AST.PrimName $ AST.NSimple aPar)])
     -- return res
     copyExpr = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
+    selSpec = AST.Function (mkVHDLExtId selId) [AST.IfaceVarDec fPar   naturalTM,
+                               AST.IfaceVarDec sPar   naturalTM,
+                               AST.IfaceVarDec nPar   naturalTM,
+                               AST.IfaceVarDec vecPar vectorTM ] vectorTM
+    -- variable res : fsvec_x (0 to n-1);
+    selVar = 
+      AST.VarDec resId 
+                (AST.SubtypeIn vectorTM
+                  (Just $ AST.ConstraintIndex $ AST.IndexConstraint 
+                    [AST.ToRange (AST.PrimLit "0")
+                      ((AST.PrimName (AST.NSimple nPar)) AST.:-:
+                      (AST.PrimLit "1"))   ])
+                )
+                Nothing
+    -- for i res'range loop
+    --   res(i) := vec(f+i*s);
+    -- end loop;
+    selFor = AST.ForSM iId (AST.AttribRange $ AST.AttribName (AST.NSimple resId) rangeId Nothing) [selAssign]
+    -- res(i) := vec(f+i*s);
+    selAssign = let origExp = AST.PrimName (AST.NSimple fPar) AST.:+: 
+                                (AST.PrimName (AST.NSimple iId) AST.:*: 
+                                  AST.PrimName (AST.NSimple sPar)) in
+                                  AST.NIndexed (AST.IndexedName (AST.NSimple resId) [AST.PrimName (AST.NSimple iId)]) AST.:=
+                                    (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
@@ -517,13 +632,20 @@ globalNameTable = Map.fromList
   , (initId           , (1, genFCall                ) )
   , (takeId           , (2, genFCall                ) )
   , (dropId           , (2, genFCall                ) )
+  , (selId            , (4, genFCall                ) )
   , (plusgtId         , (2, genFCall                ) )
+  , (ltplusId         , (2, genFCall                ) )
+  , (plusplusId       , (2, genFCall                ) )
   , (mapId            , (2, genMap                  ) )
   , (zipWithId        , (3, genZipWith              ) )
-  --, (foldlId          , (3, genFoldl                ) )
+  , (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     ) )