1 {-# LANGUAGE PackageImports #-}
3 module CLasH.VHDL.Generate where
6 import qualified Control.Monad as Monad
7 import qualified Data.Map as Map
9 import qualified Data.Either as Either
10 import qualified Control.Monad.Trans.State as State
11 import qualified "transformers" Control.Monad.Identity as Identity
13 import Data.Accessor.MonadState as MonadState
17 import qualified Language.VHDL.AST as AST
23 import qualified IdInfo
24 import qualified Literal
26 import qualified TyCon
29 import CLasH.VHDL.Constants
30 import CLasH.VHDL.VHDLTypes
31 import CLasH.VHDL.VHDLTools
32 import CLasH.Utils.Core.CoreTools
33 import CLasH.Utils.Pretty
35 -----------------------------------------------------------------------------
36 -- Functions to generate VHDL for builtin functions
37 -----------------------------------------------------------------------------
39 -- | A function to wrap a builder-like function that expects its arguments to
41 genExprArgs wrap dst func args = do
42 args' <- eitherCoreOrExprArgs args
45 eitherCoreOrExprArgs :: [Either CoreSyn.CoreExpr AST.Expr] -> VHDLSession [AST.Expr]
46 eitherCoreOrExprArgs args = mapM (Either.either ((MonadState.lift vsType) . varToVHDLExpr . exprToVar) return) args
48 -- | A function to wrap a builder-like function that expects its arguments to
51 (dst -> func -> [Var.Var] -> res)
52 -> (dst -> func -> [Either CoreSyn.CoreExpr AST.Expr] -> res)
53 genVarArgs wrap dst func args = wrap dst func args'
55 args' = map exprToVar exprargs
56 -- Check (rather crudely) that all arguments are CoreExprs
57 (exprargs, []) = Either.partitionEithers args
59 -- | A function to wrap a builder-like function that expects its arguments to
62 (dst -> func -> [Literal.Literal] -> res)
63 -> (dst -> func -> [Either CoreSyn.CoreExpr AST.Expr] -> res)
64 genLitArgs wrap dst func args = wrap dst func args'
66 args' = map exprToLit litargs
67 -- FIXME: Check if we were passed an CoreSyn.App
68 litargs = concat (map getLiterals exprargs)
69 (exprargs, []) = Either.partitionEithers args
71 -- | A function to wrap a builder-like function that produces an expression
72 -- and expects it to be assigned to the destination.
74 ((Either CoreSyn.CoreBndr AST.VHDLName) -> func -> [arg] -> VHDLSession AST.Expr)
75 -> ((Either CoreSyn.CoreBndr AST.VHDLName) -> func -> [arg] -> VHDLSession [AST.ConcSm])
76 genExprRes wrap dst func args = do
77 expr <- wrap dst func args
78 return $ [mkUncondAssign dst expr]
80 -- | Generate a binary operator application. The first argument should be a
81 -- constructor from the AST.Expr type, e.g. AST.And.
82 genOperator2 :: (AST.Expr -> AST.Expr -> AST.Expr) -> BuiltinBuilder
83 genOperator2 op = genExprArgs $ genExprRes (genOperator2' op)
84 genOperator2' :: (AST.Expr -> AST.Expr -> AST.Expr) -> dst -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr
85 genOperator2' op _ f [arg1, arg2] = return $ op arg1 arg2
87 -- | Generate a unary operator application
88 genOperator1 :: (AST.Expr -> AST.Expr) -> BuiltinBuilder
89 genOperator1 op = genExprArgs $ genExprRes (genOperator1' op)
90 genOperator1' :: (AST.Expr -> AST.Expr) -> dst -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr
91 genOperator1' op _ f [arg] = return $ op arg
93 -- | Generate a unary operator application
94 genNegation :: BuiltinBuilder
95 genNegation = genVarArgs $ genExprRes genNegation'
96 genNegation' :: dst -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession AST.Expr
97 genNegation' _ f [arg] = do
98 arg1 <- MonadState.lift vsType $ varToVHDLExpr arg
99 let ty = Var.varType arg
100 let (tycon, args) = Type.splitTyConApp ty
101 let name = Name.getOccString (TyCon.tyConName tycon)
103 "SizedInt" -> return $ AST.Neg arg1
104 otherwise -> error $ "\nGenerate.genNegation': Negation allowed for type: " ++ show name
106 -- | Generate a function call from the destination binder, function name and a
107 -- list of expressions (its arguments)
108 genFCall :: Bool -> BuiltinBuilder
109 genFCall switch = genExprArgs $ genExprRes (genFCall' switch)
110 genFCall' :: Bool -> Either CoreSyn.CoreBndr AST.VHDLName -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr
111 genFCall' switch (Left res) f args = do
112 let fname = varToString f
113 let el_ty = if switch then (Var.varType res) else ((tfvec_elem . Var.varType) res)
114 id <- MonadState.lift vsType $ vectorFunId el_ty fname
115 return $ AST.PrimFCall $ AST.FCall (AST.NSimple id) $
116 map (\exp -> Nothing AST.:=>: AST.ADExpr exp) args
117 genFCall' _ (Right name) _ _ = error $ "\nGenerate.genFCall': Cannot generate builtin function call assigned to a VHDLName: " ++ show name
119 genFromSizedWord :: BuiltinBuilder
120 genFromSizedWord = genExprArgs $ genExprRes genFromSizedWord'
121 genFromSizedWord' :: Either CoreSyn.CoreBndr AST.VHDLName -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr
122 genFromSizedWord' (Left res) f args = do
123 let fname = varToString f
124 return $ AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLBasicId toIntegerId)) $
125 map (\exp -> Nothing AST.:=>: AST.ADExpr exp) args
126 genFromSizedWord' (Right name) _ _ = error $ "\nGenerate.genFromSizedWord': Cannot generate builtin function call assigned to a VHDLName: " ++ show name
128 genResize :: BuiltinBuilder
129 genResize = genExprArgs $ genExprRes genResize'
130 genResize' :: Either CoreSyn.CoreBndr AST.VHDLName -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr
131 genResize' (Left res) f [arg] = do {
132 ; let { ty = Var.varType res
133 ; (tycon, args) = Type.splitTyConApp ty
134 ; name = Name.getOccString (TyCon.tyConName tycon)
136 ; len <- case name of
137 "SizedInt" -> MonadState.lift vsType $ tfp_to_int (sized_int_len_ty ty)
138 "SizedWord" -> MonadState.lift vsType $ tfp_to_int (sized_word_len_ty ty)
139 ; return $ AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLBasicId resizeId))
140 [Nothing AST.:=>: AST.ADExpr arg, Nothing AST.:=>: AST.ADExpr( AST.PrimLit (show len))]
142 genResize' (Right name) _ _ = error $ "\nGenerate.genFromSizedWord': Cannot generate builtin function call assigned to a VHDLName: " ++ show name
144 -- FIXME: I'm calling genLitArgs which is very specific function,
145 -- which needs to be fixed as well
146 genFromInteger :: BuiltinBuilder
147 genFromInteger = genLitArgs $ genExprRes genFromInteger'
148 genFromInteger' :: Either CoreSyn.CoreBndr AST.VHDLName -> CoreSyn.CoreBndr -> [Literal.Literal] -> VHDLSession AST.Expr
149 genFromInteger' (Left res) f lits = do {
150 ; let { ty = Var.varType res
151 ; (tycon, args) = Type.splitTyConApp ty
152 ; name = Name.getOccString (TyCon.tyConName tycon)
154 ; len <- case name of
155 "SizedInt" -> MonadState.lift vsType $ tfp_to_int (sized_int_len_ty ty)
156 "SizedWord" -> MonadState.lift vsType $ tfp_to_int (sized_word_len_ty ty)
157 ; let fname = case name of "SizedInt" -> toSignedId ; "SizedWord" -> toUnsignedId
158 ; return $ AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLBasicId fname))
159 [Nothing AST.:=>: AST.ADExpr (AST.PrimLit (show (last lits))), Nothing AST.:=>: AST.ADExpr( AST.PrimLit (show len))]
162 genFromInteger' (Right name) _ _ = error $ "\nGenerate.genFromInteger': Cannot generate builtin function call assigned to a VHDLName: " ++ show name
165 -- | Generate a generate statement for the builtin function "map"
166 genMap :: BuiltinBuilder
167 genMap (Left res) f [Left mapped_f, Left (Var arg)] = do {
168 -- mapped_f must be a CoreExpr (since we can't represent functions as VHDL
169 -- expressions). arg must be a CoreExpr (and should be a CoreSyn.Var), since
170 -- we must index it (which we couldn't if it was a VHDL Expr, since only
171 -- VHDLNames can be indexed).
172 -- Setup the generate scheme
173 ; len <- MonadState.lift vsType $ tfp_to_int $ (tfvec_len_ty . Var.varType) res
174 -- TODO: Use something better than varToString
175 ; let { label = mkVHDLExtId ("mapVector" ++ (varToString res))
176 ; n_id = mkVHDLBasicId "n"
177 ; n_expr = idToVHDLExpr n_id
178 ; range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
179 ; genScheme = AST.ForGn n_id range
180 -- Create the content of the generate statement: Applying the mapped_f to
181 -- each of the elements in arg, storing to each element in res
182 ; resname = mkIndexedName (varToVHDLName res) n_expr
183 ; argexpr = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg) n_expr
184 ; (CoreSyn.Var real_f, already_mapped_args) = CoreSyn.collectArgs mapped_f
185 ; valargs = get_val_args (Var.varType real_f) already_mapped_args
187 ; app_concsms <- genApplication (Right resname) real_f (map Left valargs ++ [Right argexpr])
188 -- Return the generate statement
189 ; return [AST.CSGSm $ AST.GenerateSm label genScheme [] app_concsms]
192 genMap' (Right name) _ _ = error $ "\nGenerate.genMap': Cannot generate map function call assigned to a VHDLName: " ++ show name
194 genZipWith :: BuiltinBuilder
195 genZipWith = genVarArgs genZipWith'
196 genZipWith' :: (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
197 genZipWith' (Left res) f args@[zipped_f, arg1, arg2] = do {
198 -- Setup the generate scheme
199 ; len <- MonadState.lift vsType $ tfp_to_int $ (tfvec_len_ty . Var.varType) res
200 -- TODO: Use something better than varToString
201 ; let { label = mkVHDLExtId ("zipWithVector" ++ (varToString res))
202 ; n_id = mkVHDLBasicId "n"
203 ; n_expr = idToVHDLExpr n_id
204 ; range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
205 ; genScheme = AST.ForGn n_id range
206 -- Create the content of the generate statement: Applying the zipped_f to
207 -- each of the elements in arg1 and arg2, storing to each element in res
208 ; resname = mkIndexedName (varToVHDLName res) n_expr
209 ; argexpr1 = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg1) n_expr
210 ; argexpr2 = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg2) n_expr
212 ; app_concsms <- genApplication (Right resname) zipped_f [Right argexpr1, Right argexpr2]
213 -- Return the generate functions
214 ; return [AST.CSGSm $ AST.GenerateSm label genScheme [] app_concsms]
217 genFoldl :: BuiltinBuilder
218 genFoldl = genFold True
220 genFoldr :: BuiltinBuilder
221 genFoldr = genFold False
223 genFold :: Bool -> BuiltinBuilder
224 genFold left = genVarArgs (genFold' left)
226 genFold' :: Bool -> (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
227 genFold' left res f args@[folded_f , start ,vec]= do
228 len <- MonadState.lift vsType $ tfp_to_int $ (tfvec_len_ty (Var.varType vec))
229 genFold'' len left res f args
231 genFold'' :: Int -> Bool -> (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
232 -- Special case for an empty input vector, just assign start to res
233 genFold'' len left (Left res) _ [_, start, vec] | len == 0 = do
234 arg <- MonadState.lift vsType $ varToVHDLExpr start
235 return [mkUncondAssign (Left res) arg]
237 genFold'' len left (Left res) f [folded_f, start, vec] = do
239 --len <- MonadState.lift vsType $ tfp_to_int $ (tfvec_len_ty . Var.varType) vec
240 -- An expression for len-1
241 let len_min_expr = (AST.PrimLit $ show (len-1))
242 -- evec is (TFVec n), so it still needs an element type
243 let (nvec, _) = splitAppTy (Var.varType vec)
244 -- Put the type of the start value in nvec, this will be the type of our
246 let tmp_ty = Type.mkAppTy nvec (Var.varType start)
247 let error_msg = "\nGenerate.genFold': Can not construct temp vector for element type: " ++ pprString tmp_ty
248 tmp_vhdl_ty <- MonadState.lift vsType $ vhdl_ty error_msg tmp_ty
249 -- Setup the generate scheme
250 let gen_label = mkVHDLExtId ("foldlVector" ++ (varToString vec))
251 let block_label = mkVHDLExtId ("foldlVector" ++ (varToString start))
252 let gen_range = if left then AST.ToRange (AST.PrimLit "0") len_min_expr
253 else AST.DownRange len_min_expr (AST.PrimLit "0")
254 let gen_scheme = AST.ForGn n_id gen_range
255 -- Make the intermediate vector
256 let tmp_dec = AST.BDISD $ AST.SigDec tmp_id tmp_vhdl_ty Nothing
257 -- Create the generate statement
258 cells <- sequence [genFirstCell, genOtherCell]
259 let gen_sm = AST.GenerateSm gen_label gen_scheme [] (map AST.CSGSm cells)
260 -- Assign tmp[len-1] or tmp[0] to res
261 let out_assign = mkUncondAssign (Left res) $ vhdlNameToVHDLExpr (if left then
262 (mkIndexedName tmp_name (AST.PrimLit $ show (len-1))) else
263 (mkIndexedName tmp_name (AST.PrimLit "0")))
264 let block = AST.BlockSm block_label [] (AST.PMapAspect []) [tmp_dec] [AST.CSGSm gen_sm, out_assign]
265 return [AST.CSBSm block]
267 -- An id for the counter
268 n_id = mkVHDLBasicId "n"
269 n_cur = idToVHDLExpr n_id
270 -- An expression for previous n
271 n_prev = if left then (n_cur AST.:-: (AST.PrimLit "1"))
272 else (n_cur AST.:+: (AST.PrimLit "1"))
273 -- An id for the tmp result vector
274 tmp_id = mkVHDLBasicId "tmp"
275 tmp_name = AST.NSimple tmp_id
276 -- Generate parts of the fold
277 genFirstCell, genOtherCell :: VHDLSession AST.GenerateSm
279 len <- MonadState.lift vsType $ tfp_to_int $ (tfvec_len_ty . Var.varType) vec
280 let cond_label = mkVHDLExtId "firstcell"
281 -- if n == 0 or n == len-1
282 let cond_scheme = AST.IfGn $ n_cur AST.:=: (if left then (AST.PrimLit "0")
283 else (AST.PrimLit $ show (len-1)))
284 -- Output to tmp[current n]
285 let resname = mkIndexedName tmp_name n_cur
287 argexpr1 <- MonadState.lift vsType $ varToVHDLExpr start
288 -- Input from vec[current n]
289 let argexpr2 = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName vec) n_cur
290 app_concsms <- genApplication (Right resname) folded_f ( if left then
291 [Right argexpr1, Right argexpr2]
293 [Right argexpr2, Right argexpr1]
295 -- Return the conditional generate part
296 return $ AST.GenerateSm cond_label cond_scheme [] app_concsms
299 len <- MonadState.lift vsType $ tfp_to_int $ (tfvec_len_ty . Var.varType) vec
300 let cond_label = mkVHDLExtId "othercell"
301 -- if n > 0 or n < len-1
302 let cond_scheme = AST.IfGn $ n_cur AST.:/=: (if left then (AST.PrimLit "0")
303 else (AST.PrimLit $ show (len-1)))
304 -- Output to tmp[current n]
305 let resname = mkIndexedName tmp_name n_cur
306 -- Input from tmp[previous n]
307 let argexpr1 = vhdlNameToVHDLExpr $ mkIndexedName tmp_name n_prev
308 -- Input from vec[current n]
309 let argexpr2 = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName vec) n_cur
310 app_concsms <- genApplication (Right resname) folded_f ( if left then
311 [Right argexpr1, Right argexpr2]
313 [Right argexpr2, Right argexpr1]
315 -- Return the conditional generate part
316 return $ AST.GenerateSm cond_label cond_scheme [] app_concsms
318 -- | Generate a generate statement for the builtin function "zip"
319 genZip :: BuiltinBuilder
320 genZip = genVarArgs genZip'
321 genZip' :: (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
322 genZip' (Left res) f args@[arg1, arg2] = do {
323 -- Setup the generate scheme
324 ; len <- MonadState.lift vsType $ tfp_to_int $ (tfvec_len_ty . Var.varType) res
325 -- TODO: Use something better than varToString
326 ; let { label = mkVHDLExtId ("zipVector" ++ (varToString res))
327 ; n_id = mkVHDLBasicId "n"
328 ; n_expr = idToVHDLExpr n_id
329 ; range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
330 ; genScheme = AST.ForGn n_id range
331 ; resname' = mkIndexedName (varToVHDLName res) n_expr
332 ; argexpr1 = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg1) n_expr
333 ; argexpr2 = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg2) n_expr
335 ; labels <- MonadState.lift vsType $ getFieldLabels (tfvec_elem (Var.varType res))
336 ; let { resnameA = mkSelectedName resname' (labels!!0)
337 ; resnameB = mkSelectedName resname' (labels!!1)
338 ; resA_assign = mkUncondAssign (Right resnameA) argexpr1
339 ; resB_assign = mkUncondAssign (Right resnameB) argexpr2
341 -- Return the generate functions
342 ; return [AST.CSGSm $ AST.GenerateSm label genScheme [] [resA_assign,resB_assign]]
345 -- | Generate a generate statement for the builtin function "unzip"
346 genUnzip :: BuiltinBuilder
347 genUnzip = genVarArgs genUnzip'
348 genUnzip' :: (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
349 genUnzip' (Left res) f args@[arg] = do {
350 -- Setup the generate scheme
351 ; len <- MonadState.lift vsType $ tfp_to_int $ (tfvec_len_ty . Var.varType) arg
352 -- TODO: Use something better than varToString
353 ; let { label = mkVHDLExtId ("unzipVector" ++ (varToString res))
354 ; n_id = mkVHDLBasicId "n"
355 ; n_expr = idToVHDLExpr n_id
356 ; range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len-1))
357 ; genScheme = AST.ForGn n_id range
358 ; resname' = varToVHDLName res
359 ; argexpr' = mkIndexedName (varToVHDLName arg) n_expr
361 ; reslabels <- MonadState.lift vsType $ getFieldLabels (Var.varType res)
362 ; arglabels <- MonadState.lift vsType $ getFieldLabels (tfvec_elem (Var.varType arg))
363 ; let { resnameA = mkIndexedName (mkSelectedName resname' (reslabels!!0)) n_expr
364 ; resnameB = mkIndexedName (mkSelectedName resname' (reslabels!!1)) n_expr
365 ; argexprA = vhdlNameToVHDLExpr $ mkSelectedName argexpr' (arglabels!!0)
366 ; argexprB = vhdlNameToVHDLExpr $ mkSelectedName argexpr' (arglabels!!1)
367 ; resA_assign = mkUncondAssign (Right resnameA) argexprA
368 ; resB_assign = mkUncondAssign (Right resnameB) argexprB
370 -- Return the generate functions
371 ; return [AST.CSGSm $ AST.GenerateSm label genScheme [] [resA_assign,resB_assign]]
374 genCopy :: BuiltinBuilder
375 genCopy = genVarArgs genCopy'
376 genCopy' :: (Either CoreSyn.CoreBndr AST.VHDLName ) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
377 genCopy' (Left res) f args@[arg] =
379 resExpr = AST.Aggregate [AST.ElemAssoc (Just AST.Others)
380 (AST.PrimName $ (varToVHDLName arg))]
381 out_assign = mkUncondAssign (Left res) resExpr
385 genConcat :: BuiltinBuilder
386 genConcat = genVarArgs genConcat'
387 genConcat' :: (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
388 genConcat' (Left res) f args@[arg] = do {
389 -- Setup the generate scheme
390 ; len1 <- MonadState.lift vsType $ tfp_to_int $ (tfvec_len_ty . Var.varType) arg
391 ; let (_, nvec) = splitAppTy (Var.varType arg)
392 ; len2 <- MonadState.lift vsType $ tfp_to_int $ tfvec_len_ty nvec
393 -- TODO: Use something better than varToString
394 ; let { label = mkVHDLExtId ("concatVector" ++ (varToString res))
395 ; n_id = mkVHDLBasicId "n"
396 ; n_expr = idToVHDLExpr n_id
397 ; fromRange = n_expr AST.:*: (AST.PrimLit $ show len2)
398 ; genScheme = AST.ForGn n_id range
399 -- Create the content of the generate statement: Applying the mapped_f to
400 -- each of the elements in arg, storing to each element in res
401 ; toRange = (n_expr AST.:*: (AST.PrimLit $ show len2)) AST.:+: (AST.PrimLit $ show (len2-1))
402 ; range = AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len1-1))
403 ; resname = vecSlice fromRange toRange
404 ; argexpr = vhdlNameToVHDLExpr $ mkIndexedName (varToVHDLName arg) n_expr
405 ; out_assign = mkUncondAssign (Right resname) argexpr
407 -- Return the generate statement
408 ; return [AST.CSGSm $ AST.GenerateSm label genScheme [] [out_assign]]
411 vecSlice init last = AST.NSlice (AST.SliceName (varToVHDLName res)
412 (AST.ToRange init last))
414 genIteraten :: BuiltinBuilder
415 genIteraten dst f args = genIterate dst f (tail args)
417 genIterate :: BuiltinBuilder
418 genIterate = genIterateOrGenerate True
420 genGeneraten :: BuiltinBuilder
421 genGeneraten dst f args = genGenerate dst f (tail args)
423 genGenerate :: BuiltinBuilder
424 genGenerate = genIterateOrGenerate False
426 genIterateOrGenerate :: Bool -> BuiltinBuilder
427 genIterateOrGenerate iter = genVarArgs (genIterateOrGenerate' iter)
429 genIterateOrGenerate' :: Bool -> (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
430 genIterateOrGenerate' iter (Left res) f args = do
431 len <- MonadState.lift vsType $ tfp_to_int ((tfvec_len_ty . Var.varType) res)
432 genIterateOrGenerate'' len iter (Left res) f args
434 genIterateOrGenerate'' :: Int -> Bool -> (Either CoreSyn.CoreBndr AST.VHDLName) -> CoreSyn.CoreBndr -> [Var.Var] -> VHDLSession [AST.ConcSm]
435 -- Special case for an empty input vector, just assign start to res
436 genIterateOrGenerate'' len iter (Left res) _ [app_f, start] | len == 0 = return [mkUncondAssign (Left res) (AST.PrimLit "\"\"")]
438 genIterateOrGenerate'' len iter (Left res) f [app_f, start] = do
440 -- len <- MonadState.lift vsType $ tfp_to_int ((tfvec_len_ty . Var.varType) res)
441 -- An expression for len-1
442 let len_min_expr = (AST.PrimLit $ show (len-1))
443 -- -- evec is (TFVec n), so it still needs an element type
444 -- let (nvec, _) = splitAppTy (Var.varType vec)
445 -- -- Put the type of the start value in nvec, this will be the type of our
446 -- -- temporary vector
447 let tmp_ty = Var.varType res
448 let error_msg = "\nGenerate.genFold': Can not construct temp vector for element type: " ++ pprString tmp_ty
449 tmp_vhdl_ty <- MonadState.lift vsType $ vhdl_ty error_msg tmp_ty
450 -- Setup the generate scheme
451 let gen_label = mkVHDLExtId ("iterateVector" ++ (varToString start))
452 let block_label = mkVHDLExtId ("iterateVector" ++ (varToString res))
453 let gen_range = AST.ToRange (AST.PrimLit "0") len_min_expr
454 let gen_scheme = AST.ForGn n_id gen_range
455 -- Make the intermediate vector
456 let tmp_dec = AST.BDISD $ AST.SigDec tmp_id tmp_vhdl_ty Nothing
457 -- Create the generate statement
458 cells <- sequence [genFirstCell, genOtherCell]
459 let gen_sm = AST.GenerateSm gen_label gen_scheme [] (map AST.CSGSm cells)
460 -- Assign tmp[len-1] or tmp[0] to res
461 let out_assign = mkUncondAssign (Left res) $ vhdlNameToVHDLExpr tmp_name
462 let block = AST.BlockSm block_label [] (AST.PMapAspect []) [tmp_dec] [AST.CSGSm gen_sm, out_assign]
463 return [AST.CSBSm block]
465 -- An id for the counter
466 n_id = mkVHDLBasicId "n"
467 n_cur = idToVHDLExpr n_id
468 -- An expression for previous n
469 n_prev = n_cur AST.:-: (AST.PrimLit "1")
470 -- An id for the tmp result vector
471 tmp_id = mkVHDLBasicId "tmp"
472 tmp_name = AST.NSimple tmp_id
473 -- Generate parts of the fold
474 genFirstCell, genOtherCell :: VHDLSession AST.GenerateSm
476 let cond_label = mkVHDLExtId "firstcell"
477 -- if n == 0 or n == len-1
478 let cond_scheme = AST.IfGn $ n_cur AST.:=: (AST.PrimLit "0")
479 -- Output to tmp[current n]
480 let resname = mkIndexedName tmp_name n_cur
482 argexpr <- MonadState.lift vsType $ varToVHDLExpr start
483 let startassign = mkUncondAssign (Right resname) argexpr
484 app_concsms <- genApplication (Right resname) app_f [Right argexpr]
485 -- Return the conditional generate part
486 return $ AST.GenerateSm cond_label cond_scheme [] (if iter then
493 let cond_label = mkVHDLExtId "othercell"
494 -- if n > 0 or n < len-1
495 let cond_scheme = AST.IfGn $ n_cur AST.:/=: (AST.PrimLit "0")
496 -- Output to tmp[current n]
497 let resname = mkIndexedName tmp_name n_cur
498 -- Input from tmp[previous n]
499 let argexpr = vhdlNameToVHDLExpr $ mkIndexedName tmp_name n_prev
500 app_concsms <- genApplication (Right resname) app_f [Right argexpr]
501 -- Return the conditional generate part
502 return $ AST.GenerateSm cond_label cond_scheme [] app_concsms
505 -----------------------------------------------------------------------------
506 -- Function to generate VHDL for applications
507 -----------------------------------------------------------------------------
509 (Either CoreSyn.CoreBndr AST.VHDLName) -- ^ Where to store the result?
510 -> CoreSyn.CoreBndr -- ^ The function to apply
511 -> [Either CoreSyn.CoreExpr AST.Expr] -- ^ The arguments to apply
512 -> VHDLSession [AST.ConcSm] -- ^ The resulting concurrent statements
513 genApplication dst f args = do
514 case Var.isGlobalId f of
516 signatures <- getA vsSignatures
517 -- This is a local id, so it should be a function whose definition we
518 -- have and which can be turned into a component instantiation.
519 case (Map.lookup f signatures) of
521 args' <- eitherCoreOrExprArgs args
522 -- We have a signature, this is a top level binding. Generate a
523 -- component instantiation.
524 let entity_id = ent_id signature
525 -- TODO: Using show here isn't really pretty, but we'll need some
526 -- unique-ish value...
527 let label = "comp_ins_" ++ (either show prettyShow) dst
528 let portmaps = mkAssocElems args' ((either varToVHDLName id) dst) signature
529 return [mkComponentInst label entity_id portmaps]
531 -- No signature, so this must be a local variable reference. It
532 -- should have a representable type (and thus, no arguments) and a
533 -- signal should be generated for it. Just generate an
534 -- unconditional assignment here.
535 f' <- MonadState.lift vsType $ varToVHDLExpr f
536 return $ [mkUncondAssign dst f']
538 case Var.idDetails f of
539 IdInfo.DataConWorkId dc -> case dst of
540 -- It's a datacon. Create a record from its arguments.
542 -- We have the bndr, so we can get at the type
543 labels <- MonadState.lift vsType $ getFieldLabels (Var.varType bndr)
544 args' <- eitherCoreOrExprArgs args
545 return $ zipWith mkassign labels $ args'
547 mkassign :: AST.VHDLId -> AST.Expr -> AST.ConcSm
549 let sel_name = mkSelectedName ((either varToVHDLName id) dst) label in
550 mkUncondAssign (Right sel_name) arg
551 Right _ -> error $ "\nGenerate.genApplication: Can't generate dataconstructor application without an original binder"
552 IdInfo.VanillaId -> do
553 -- It's a global value imported from elsewhere. These can be builtin
554 -- functions. Look up the function name in the name table and execute
555 -- the associated builder if there is any and the argument count matches
556 -- (this should always be the case if it typechecks, but just to be
558 case (Map.lookup (varToString f) globalNameTable) of
559 Just (arg_count, builder) ->
560 if length args == arg_count then
563 error $ "\nGenerate.genApplication(VanillaGlobal): Incorrect number of arguments to builtin function: " ++ pprString f ++ " Args: " ++ show args
564 Nothing -> error $ "\nGenerate.genApplication(VanillaGlobal): Using function from another module that is not a known builtin: " ++ pprString f
565 IdInfo.ClassOpId cls -> do
566 -- FIXME: Not looking for what instance this class op is called for
567 -- Is quite stupid of course.
568 case (Map.lookup (varToString f) globalNameTable) of
569 Just (arg_count, builder) ->
570 if length args == arg_count then
573 error $ "\nGenerate.genApplication(ClassOpId): Incorrect number of arguments to builtin function: " ++ pprString f ++ " Args: " ++ show args
574 Nothing -> error $ "\nGenerate.genApplication(ClassOpId): Using function from another module that is not a known builtin: " ++ pprString f
575 details -> error $ "\nGenerate.genApplication: Calling unsupported function " ++ pprString f ++ " with GlobalIdDetails " ++ pprString details
577 -----------------------------------------------------------------------------
578 -- Functions to generate functions dealing with vectors.
579 -----------------------------------------------------------------------------
581 -- Returns the VHDLId of the vector function with the given name for the given
582 -- element type. Generates -- this function if needed.
583 vectorFunId :: Type.Type -> String -> TypeSession AST.VHDLId
584 vectorFunId el_ty fname = do
585 let error_msg = "\nGenerate.vectorFunId: Can not construct vector function for element: " ++ pprString el_ty
586 elemTM <- vhdl_ty error_msg el_ty
587 -- TODO: This should not be duplicated from mk_vector_ty. Probably but it in
588 -- the VHDLState or something.
589 let vectorTM = mkVHDLExtId $ "vector_" ++ (AST.fromVHDLId elemTM)
590 typefuns <- getA vsTypeFuns
591 case Map.lookup (OrdType el_ty, fname) typefuns of
592 -- Function already generated, just return it
593 Just (id, _) -> return id
594 -- Function not generated yet, generate it
596 let functions = genUnconsVectorFuns elemTM vectorTM
597 case lookup fname functions of
599 modA vsTypeFuns $ Map.insert (OrdType el_ty, fname) (function_id, (fst body))
600 mapM_ (vectorFunId el_ty) (snd body)
602 Nothing -> error $ "\nGenerate.vectorFunId: I don't know how to generate vector function " ++ fname
604 function_id = mkVHDLExtId fname
606 genUnconsVectorFuns :: AST.TypeMark -- ^ type of the vector elements
607 -> AST.TypeMark -- ^ type of the vector
608 -> [(String, (AST.SubProgBody, [String]))]
609 genUnconsVectorFuns elemTM vectorTM =
610 [ (exId, (AST.SubProgBody exSpec [] [exExpr],[]))
611 , (replaceId, (AST.SubProgBody replaceSpec [AST.SPVD replaceVar] [replaceExpr,replaceRet],[]))
612 , (headId, (AST.SubProgBody headSpec [] [headExpr],[]))
613 , (lastId, (AST.SubProgBody lastSpec [] [lastExpr],[]))
614 , (initId, (AST.SubProgBody initSpec [AST.SPVD initVar] [initExpr, initRet],[]))
615 , (tailId, (AST.SubProgBody tailSpec [AST.SPVD tailVar] [tailExpr, tailRet],[]))
616 , (takeId, (AST.SubProgBody takeSpec [AST.SPVD takeVar] [takeExpr, takeRet],[]))
617 , (dropId, (AST.SubProgBody dropSpec [AST.SPVD dropVar] [dropExpr, dropRet],[]))
618 , (plusgtId, (AST.SubProgBody plusgtSpec [AST.SPVD plusgtVar] [plusgtExpr, plusgtRet],[]))
619 , (emptyId, (AST.SubProgBody emptySpec [AST.SPCD emptyVar] [emptyExpr],[]))
620 , (singletonId, (AST.SubProgBody singletonSpec [AST.SPVD singletonVar] [singletonRet],[]))
621 , (copynId, (AST.SubProgBody copynSpec [AST.SPVD copynVar] [copynExpr],[]))
622 , (selId, (AST.SubProgBody selSpec [AST.SPVD selVar] [selFor, selRet],[]))
623 , (ltplusId, (AST.SubProgBody ltplusSpec [AST.SPVD ltplusVar] [ltplusExpr, ltplusRet],[]))
624 , (plusplusId, (AST.SubProgBody plusplusSpec [AST.SPVD plusplusVar] [plusplusExpr, plusplusRet],[]))
625 , (lengthTId, (AST.SubProgBody lengthTSpec [] [lengthTExpr],[]))
626 , (shiftlId, (AST.SubProgBody shiftlSpec [AST.SPVD shiftlVar] [shiftlExpr, shiftlRet], [initId]))
627 , (shiftrId, (AST.SubProgBody shiftrSpec [AST.SPVD shiftrVar] [shiftrExpr, shiftrRet], [tailId]))
628 , (nullId, (AST.SubProgBody nullSpec [] [nullExpr], []))
629 , (rotlId, (AST.SubProgBody rotlSpec [AST.SPVD rotlVar] [rotlExpr, rotlRet], [nullId, lastId, initId]))
630 , (rotrId, (AST.SubProgBody rotrSpec [AST.SPVD rotrVar] [rotrExpr, rotrRet], [nullId, tailId, headId]))
631 , (reverseId, (AST.SubProgBody reverseSpec [AST.SPVD reverseVar] [reverseFor, reverseRet], []))
634 ixPar = AST.unsafeVHDLBasicId "ix"
635 vecPar = AST.unsafeVHDLBasicId "vec"
636 vec1Par = AST.unsafeVHDLBasicId "vec1"
637 vec2Par = AST.unsafeVHDLBasicId "vec2"
638 nPar = AST.unsafeVHDLBasicId "n"
639 iId = AST.unsafeVHDLBasicId "i"
641 aPar = AST.unsafeVHDLBasicId "a"
642 fPar = AST.unsafeVHDLBasicId "f"
643 sPar = AST.unsafeVHDLBasicId "s"
644 resId = AST.unsafeVHDLBasicId "res"
645 exSpec = AST.Function (mkVHDLExtId exId) [AST.IfaceVarDec vecPar vectorTM,
646 AST.IfaceVarDec ixPar naturalTM] elemTM
647 exExpr = AST.ReturnSm (Just $ AST.PrimName $ AST.NIndexed
648 (AST.IndexedName (AST.NSimple vecPar) [AST.PrimName $
650 replaceSpec = AST.Function (mkVHDLExtId replaceId) [ AST.IfaceVarDec vecPar vectorTM
651 , AST.IfaceVarDec iPar naturalTM
652 , AST.IfaceVarDec aPar elemTM
654 -- variable res : fsvec_x (0 to vec'length-1);
657 (AST.SubtypeIn vectorTM
658 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
659 [AST.ToRange (AST.PrimLit "0")
660 (AST.PrimName (AST.NAttribute $
661 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:-:
662 (AST.PrimLit "1")) ]))
664 -- res AST.:= vec(0 to i-1) & a & vec(i+1 to length'vec-1)
665 replaceExpr = AST.NSimple resId AST.:=
666 (vecSlice (AST.PrimLit "0") (AST.PrimName (AST.NSimple iPar) AST.:-: AST.PrimLit "1") AST.:&:
667 AST.PrimName (AST.NSimple aPar) AST.:&:
668 vecSlice (AST.PrimName (AST.NSimple iPar) AST.:+: AST.PrimLit "1")
669 ((AST.PrimName (AST.NAttribute $
670 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing))
671 AST.:-: AST.PrimLit "1"))
672 replaceRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
673 vecSlice init last = AST.PrimName (AST.NSlice
676 (AST.ToRange init last)))
677 headSpec = AST.Function (mkVHDLExtId headId) [AST.IfaceVarDec vecPar vectorTM] elemTM
679 headExpr = AST.ReturnSm (Just $ (AST.PrimName $ AST.NIndexed (AST.IndexedName
680 (AST.NSimple vecPar) [AST.PrimLit "0"])))
681 lastSpec = AST.Function (mkVHDLExtId lastId) [AST.IfaceVarDec vecPar vectorTM] elemTM
682 -- return vec(vec'length-1);
683 lastExpr = AST.ReturnSm (Just $ (AST.PrimName $ AST.NIndexed (AST.IndexedName
685 [AST.PrimName (AST.NAttribute $
686 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing)
687 AST.:-: AST.PrimLit "1"])))
688 initSpec = AST.Function (mkVHDLExtId initId) [AST.IfaceVarDec vecPar vectorTM] vectorTM
689 -- variable res : fsvec_x (0 to vec'length-2);
692 (AST.SubtypeIn vectorTM
693 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
694 [AST.ToRange (AST.PrimLit "0")
695 (AST.PrimName (AST.NAttribute $
696 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:-:
697 (AST.PrimLit "2")) ]))
699 -- resAST.:= vec(0 to vec'length-2)
700 initExpr = AST.NSimple resId AST.:= (vecSlice
702 (AST.PrimName (AST.NAttribute $
703 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing)
704 AST.:-: AST.PrimLit "2"))
705 initRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
706 tailSpec = AST.Function (mkVHDLExtId tailId) [AST.IfaceVarDec vecPar vectorTM] vectorTM
707 -- variable res : fsvec_x (0 to vec'length-2);
710 (AST.SubtypeIn vectorTM
711 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
712 [AST.ToRange (AST.PrimLit "0")
713 (AST.PrimName (AST.NAttribute $
714 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:-:
715 (AST.PrimLit "2")) ]))
717 -- res AST.:= vec(1 to vec'length-1)
718 tailExpr = AST.NSimple resId AST.:= (vecSlice
720 (AST.PrimName (AST.NAttribute $
721 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing)
722 AST.:-: AST.PrimLit "1"))
723 tailRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
724 takeSpec = AST.Function (mkVHDLExtId takeId) [AST.IfaceVarDec nPar naturalTM,
725 AST.IfaceVarDec vecPar vectorTM ] vectorTM
726 -- variable res : fsvec_x (0 to n-1);
729 (AST.SubtypeIn vectorTM
730 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
731 [AST.ToRange (AST.PrimLit "0")
732 ((AST.PrimName (AST.NSimple nPar)) AST.:-:
733 (AST.PrimLit "1")) ]))
735 -- res AST.:= vec(0 to n-1)
736 takeExpr = AST.NSimple resId AST.:=
737 (vecSlice (AST.PrimLit "1")
738 (AST.PrimName (AST.NSimple $ nPar) AST.:-: AST.PrimLit "1"))
739 takeRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
740 dropSpec = AST.Function (mkVHDLExtId dropId) [AST.IfaceVarDec nPar naturalTM,
741 AST.IfaceVarDec vecPar vectorTM ] vectorTM
742 -- variable res : fsvec_x (0 to vec'length-n-1);
745 (AST.SubtypeIn vectorTM
746 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
747 [AST.ToRange (AST.PrimLit "0")
748 (AST.PrimName (AST.NAttribute $
749 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:-:
750 (AST.PrimName $ AST.NSimple nPar)AST.:-: (AST.PrimLit "1")) ]))
752 -- res AST.:= vec(n to vec'length-1)
753 dropExpr = AST.NSimple resId AST.:= (vecSlice
754 (AST.PrimName $ AST.NSimple nPar)
755 (AST.PrimName (AST.NAttribute $
756 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing)
757 AST.:-: AST.PrimLit "1"))
758 dropRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
759 plusgtSpec = AST.Function (mkVHDLExtId plusgtId) [AST.IfaceVarDec aPar elemTM,
760 AST.IfaceVarDec vecPar vectorTM] vectorTM
761 -- variable res : fsvec_x (0 to vec'length);
764 (AST.SubtypeIn vectorTM
765 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
766 [AST.ToRange (AST.PrimLit "0")
767 (AST.PrimName (AST.NAttribute $
768 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing))]))
770 plusgtExpr = AST.NSimple resId AST.:=
771 ((AST.PrimName $ AST.NSimple aPar) AST.:&:
772 (AST.PrimName $ AST.NSimple vecPar))
773 plusgtRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
774 emptySpec = AST.Function (mkVHDLExtId emptyId) [] vectorTM
777 (AST.SubtypeIn vectorTM Nothing)
778 (Just $ AST.PrimLit "\"\"")
779 emptyExpr = AST.ReturnSm (Just $ AST.PrimName (AST.NSimple resId))
780 singletonSpec = AST.Function (mkVHDLExtId singletonId) [AST.IfaceVarDec aPar elemTM ]
782 -- variable res : fsvec_x (0 to 0) := (others => a);
785 (AST.SubtypeIn vectorTM
786 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
787 [AST.ToRange (AST.PrimLit "0") (AST.PrimLit "0")]))
788 (Just $ AST.Aggregate [AST.ElemAssoc (Just AST.Others)
789 (AST.PrimName $ AST.NSimple aPar)])
790 singletonRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
791 copynSpec = AST.Function (mkVHDLExtId copynId) [AST.IfaceVarDec nPar naturalTM,
792 AST.IfaceVarDec aPar elemTM ] vectorTM
793 -- variable res : fsvec_x (0 to n-1) := (others => a);
796 (AST.SubtypeIn vectorTM
797 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
798 [AST.ToRange (AST.PrimLit "0")
799 ((AST.PrimName (AST.NSimple nPar)) AST.:-:
800 (AST.PrimLit "1")) ]))
801 (Just $ AST.Aggregate [AST.ElemAssoc (Just AST.Others)
802 (AST.PrimName $ AST.NSimple aPar)])
804 copynExpr = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
805 selSpec = AST.Function (mkVHDLExtId selId) [AST.IfaceVarDec fPar naturalTM,
806 AST.IfaceVarDec sPar naturalTM,
807 AST.IfaceVarDec nPar naturalTM,
808 AST.IfaceVarDec vecPar vectorTM ] vectorTM
809 -- variable res : fsvec_x (0 to n-1);
812 (AST.SubtypeIn vectorTM
813 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
814 [AST.ToRange (AST.PrimLit "0")
815 ((AST.PrimName (AST.NSimple nPar)) AST.:-:
816 (AST.PrimLit "1")) ])
819 -- for i res'range loop
820 -- res(i) := vec(f+i*s);
822 selFor = AST.ForSM iId (AST.AttribRange $ AST.AttribName (AST.NSimple resId) rangeId Nothing) [selAssign]
823 -- res(i) := vec(f+i*s);
824 selAssign = let origExp = AST.PrimName (AST.NSimple fPar) AST.:+:
825 (AST.PrimName (AST.NSimple iId) AST.:*:
826 AST.PrimName (AST.NSimple sPar)) in
827 AST.NIndexed (AST.IndexedName (AST.NSimple resId) [AST.PrimName (AST.NSimple iId)]) AST.:=
828 (AST.PrimName $ AST.NIndexed (AST.IndexedName (AST.NSimple vecPar) [origExp]))
830 selRet = AST.ReturnSm (Just $ AST.PrimName (AST.NSimple resId))
831 ltplusSpec = AST.Function (mkVHDLExtId ltplusId) [AST.IfaceVarDec vecPar vectorTM,
832 AST.IfaceVarDec aPar elemTM] vectorTM
833 -- variable res : fsvec_x (0 to vec'length);
836 (AST.SubtypeIn vectorTM
837 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
838 [AST.ToRange (AST.PrimLit "0")
839 (AST.PrimName (AST.NAttribute $
840 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing))]))
842 ltplusExpr = AST.NSimple resId AST.:=
843 ((AST.PrimName $ AST.NSimple vecPar) AST.:&:
844 (AST.PrimName $ AST.NSimple aPar))
845 ltplusRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
846 plusplusSpec = AST.Function (mkVHDLExtId plusplusId) [AST.IfaceVarDec vec1Par vectorTM,
847 AST.IfaceVarDec vec2Par vectorTM]
849 -- variable res : fsvec_x (0 to vec1'length + vec2'length -1);
852 (AST.SubtypeIn vectorTM
853 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
854 [AST.ToRange (AST.PrimLit "0")
855 (AST.PrimName (AST.NAttribute $
856 AST.AttribName (AST.NSimple vec1Par) (mkVHDLBasicId lengthId) Nothing) AST.:+:
857 AST.PrimName (AST.NAttribute $
858 AST.AttribName (AST.NSimple vec2Par) (mkVHDLBasicId lengthId) Nothing) AST.:-:
861 plusplusExpr = AST.NSimple resId AST.:=
862 ((AST.PrimName $ AST.NSimple vec1Par) AST.:&:
863 (AST.PrimName $ AST.NSimple vec2Par))
864 plusplusRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
865 lengthTSpec = AST.Function (mkVHDLExtId lengthTId) [AST.IfaceVarDec vecPar vectorTM] naturalTM
866 lengthTExpr = AST.ReturnSm (Just $ AST.PrimName (AST.NAttribute $
867 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing))
868 shiftlSpec = AST.Function (mkVHDLExtId shiftlId) [AST.IfaceVarDec vecPar vectorTM,
869 AST.IfaceVarDec aPar elemTM ] vectorTM
870 -- variable res : fsvec_x (0 to vec'length-1);
873 (AST.SubtypeIn vectorTM
874 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
875 [AST.ToRange (AST.PrimLit "0")
876 (AST.PrimName (AST.NAttribute $
877 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:-:
878 (AST.PrimLit "1")) ]))
880 -- res := a & init(vec)
881 shiftlExpr = AST.NSimple resId AST.:=
882 (AST.PrimName (AST.NSimple aPar) AST.:&:
883 (AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLExtId initId))
884 [Nothing AST.:=>: AST.ADExpr (AST.PrimName $ AST.NSimple vecPar)]))
885 shiftlRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
886 shiftrSpec = AST.Function (mkVHDLExtId shiftrId) [AST.IfaceVarDec vecPar vectorTM,
887 AST.IfaceVarDec aPar elemTM ] vectorTM
888 -- variable res : fsvec_x (0 to vec'length-1);
891 (AST.SubtypeIn vectorTM
892 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
893 [AST.ToRange (AST.PrimLit "0")
894 (AST.PrimName (AST.NAttribute $
895 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:-:
896 (AST.PrimLit "1")) ]))
898 -- res := tail(vec) & a
899 shiftrExpr = AST.NSimple resId AST.:=
900 ((AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLExtId tailId))
901 [Nothing AST.:=>: AST.ADExpr (AST.PrimName $ AST.NSimple vecPar)]) AST.:&:
902 (AST.PrimName (AST.NSimple aPar)))
904 shiftrRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
905 nullSpec = AST.Function (mkVHDLExtId nullId) [AST.IfaceVarDec vecPar vectorTM] booleanTM
906 -- return vec'length = 0
907 nullExpr = AST.ReturnSm (Just $
908 AST.PrimName (AST.NAttribute $
909 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:=:
911 rotlSpec = AST.Function (mkVHDLExtId rotlId) [AST.IfaceVarDec vecPar vectorTM] vectorTM
912 -- variable res : fsvec_x (0 to vec'length-1);
915 (AST.SubtypeIn vectorTM
916 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
917 [AST.ToRange (AST.PrimLit "0")
918 (AST.PrimName (AST.NAttribute $
919 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:-:
920 (AST.PrimLit "1")) ]))
922 -- if null(vec) then res := vec else res := last(vec) & init(vec)
923 rotlExpr = AST.IfSm (AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLExtId nullId))
924 [Nothing AST.:=>: AST.ADExpr (AST.PrimName $ AST.NSimple vecPar)])
925 [AST.NSimple resId AST.:= (AST.PrimName $ AST.NSimple vecPar)]
927 (Just $ AST.Else [rotlExprRet])
929 AST.NSimple resId AST.:=
930 ((AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLExtId lastId))
931 [Nothing AST.:=>: AST.ADExpr (AST.PrimName $ AST.NSimple vecPar)]) AST.:&:
932 (AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLExtId initId))
933 [Nothing AST.:=>: AST.ADExpr (AST.PrimName $ AST.NSimple vecPar)]))
934 rotlRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
935 rotrSpec = AST.Function (mkVHDLExtId rotrId) [AST.IfaceVarDec vecPar vectorTM] vectorTM
936 -- variable res : fsvec_x (0 to vec'length-1);
939 (AST.SubtypeIn vectorTM
940 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
941 [AST.ToRange (AST.PrimLit "0")
942 (AST.PrimName (AST.NAttribute $
943 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:-:
944 (AST.PrimLit "1")) ]))
946 -- if null(vec) then res := vec else res := tail(vec) & head(vec)
947 rotrExpr = AST.IfSm (AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLExtId nullId))
948 [Nothing AST.:=>: AST.ADExpr (AST.PrimName $ AST.NSimple vecPar)])
949 [AST.NSimple resId AST.:= (AST.PrimName $ AST.NSimple vecPar)]
951 (Just $ AST.Else [rotrExprRet])
953 AST.NSimple resId AST.:=
954 ((AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLExtId tailId))
955 [Nothing AST.:=>: AST.ADExpr (AST.PrimName $ AST.NSimple vecPar)]) AST.:&:
956 (AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLExtId headId))
957 [Nothing AST.:=>: AST.ADExpr (AST.PrimName $ AST.NSimple vecPar)]))
958 rotrRet = AST.ReturnSm (Just $ AST.PrimName $ AST.NSimple resId)
959 reverseSpec = AST.Function (mkVHDLExtId reverseId) [AST.IfaceVarDec vecPar vectorTM] vectorTM
962 (AST.SubtypeIn vectorTM
963 (Just $ AST.ConstraintIndex $ AST.IndexConstraint
964 [AST.ToRange (AST.PrimLit "0")
965 (AST.PrimName (AST.NAttribute $
966 AST.AttribName (AST.NSimple vecPar) (mkVHDLBasicId lengthId) Nothing) AST.:-:
967 (AST.PrimLit "1")) ]))
969 -- for i in 0 to res'range loop
970 -- res(vec'length-i-1) := vec(i);
973 AST.ForSM iId (AST.AttribRange $ AST.AttribName (AST.NSimple resId) rangeId Nothing) [reverseAssign]
974 -- res(vec'length-i-1) := vec(i);
975 reverseAssign = AST.NIndexed (AST.IndexedName (AST.NSimple resId) [destExp]) AST.:=
976 (AST.PrimName $ AST.NIndexed (AST.IndexedName (AST.NSimple vecPar)
977 [AST.PrimName $ AST.NSimple iId]))
978 where destExp = AST.PrimName (AST.NAttribute $ AST.AttribName (AST.NSimple vecPar)
979 (mkVHDLBasicId lengthId) Nothing) AST.:-:
980 AST.PrimName (AST.NSimple iId) AST.:-:
983 reverseRet = AST.ReturnSm (Just $ AST.PrimName (AST.NSimple resId))
985 -----------------------------------------------------------------------------
986 -- A table of builtin functions
987 -----------------------------------------------------------------------------
989 -- | The builtin functions we support. Maps a name to an argument count and a
991 globalNameTable :: NameTable
992 globalNameTable = Map.fromList
993 [ (exId , (2, genFCall False ) )
994 , (replaceId , (3, genFCall False ) )
995 , (headId , (1, genFCall True ) )
996 , (lastId , (1, genFCall True ) )
997 , (tailId , (1, genFCall False ) )
998 , (initId , (1, genFCall False ) )
999 , (takeId , (2, genFCall False ) )
1000 , (dropId , (2, genFCall False ) )
1001 , (selId , (4, genFCall False ) )
1002 , (plusgtId , (2, genFCall False ) )
1003 , (ltplusId , (2, genFCall False ) )
1004 , (plusplusId , (2, genFCall False ) )
1005 , (mapId , (2, genMap ) )
1006 , (zipWithId , (3, genZipWith ) )
1007 , (foldlId , (3, genFoldl ) )
1008 , (foldrId , (3, genFoldr ) )
1009 , (zipId , (2, genZip ) )
1010 , (unzipId , (1, genUnzip ) )
1011 , (shiftlId , (2, genFCall False ) )
1012 , (shiftrId , (2, genFCall False ) )
1013 , (rotlId , (1, genFCall False ) )
1014 , (rotrId , (1, genFCall False ) )
1015 , (concatId , (1, genConcat ) )
1016 , (reverseId , (1, genFCall False ) )
1017 , (iteratenId , (3, genIteraten ) )
1018 , (iterateId , (2, genIterate ) )
1019 , (generatenId , (3, genGeneraten ) )
1020 , (generateId , (2, genGenerate ) )
1021 , (emptyId , (0, genFCall False ) )
1022 , (singletonId , (1, genFCall False ) )
1023 , (copynId , (2, genFCall False ) )
1024 , (copyId , (1, genCopy ) )
1025 , (lengthTId , (1, genFCall False ) )
1026 , (nullId , (1, genFCall False ) )
1027 , (hwxorId , (2, genOperator2 AST.Xor ) )
1028 , (hwandId , (2, genOperator2 AST.And ) )
1029 , (hworId , (2, genOperator2 AST.Or ) )
1030 , (hwnotId , (1, genOperator1 AST.Not ) )
1031 , (plusId , (2, genOperator2 (AST.:+:) ) )
1032 , (timesId , (2, genOperator2 (AST.:*:) ) )
1033 , (negateId , (1, genNegation ) )
1034 , (minusId , (2, genOperator2 (AST.:-:) ) )
1035 , (fromSizedWordId , (1, genFromSizedWord ) )
1036 , (fromIntegerId , (1, genFromInteger ) )
1037 , (resizeId , (1, genResize ) )