lengthTId :: String
lengthTId = "lengthT"
+-- Numeric Operations
+
+-- | plus operation identifier
+plusId :: String
+plusId = "+"
+
+-- | times operation identifier
+timesId :: String
+timesId = "*"
+
+-- | negate operation identifier
+negateId :: String
+negateId = "negate"
+
+-- | minus operation identifier
+minusId :: String
+minusId = "-"
+
+-- | convert sizedword to ranged
+fromSizedWordId :: String
+fromSizedWordId = "fromSizedWord"
+
+toIntegerId :: String
+toIntegerId = "to_integer"
+
------------------
-- VHDL type marks
------------------
-- | integer TypeMark
integerTM :: AST.TypeMark
integerTM = AST.unsafeVHDLBasicId "integer"
+
+-- | signed TypeMark
+signedTM :: AST.TypeMark
+signedTM = AST.unsafeVHDLBasicId "signed"
+
+-- | unsigned TypeMark
+unsignedTM :: AST.TypeMark
+unsignedTM = AST.unsafeVHDLBasicId "unsigned"
map (\exp -> Nothing AST.:=>: AST.ADExpr exp) args
genFCall' _ (Right name) _ _ = error $ "\nGenerate.genFCall': Cannot generate builtin function call assigned to a VHDLName: " ++ show name
+genFromSizedWord :: BuiltinBuilder
+genFromSizedWord = genExprArgs $ genExprRes genFromSizedWord'
+genFromSizedWord' :: Either CoreSyn.CoreBndr AST.VHDLName -> CoreSyn.CoreBndr -> [AST.Expr] -> VHDLSession AST.Expr
+genFromSizedWord' (Left res) f args = do
+ let fname = varToString f
+ return $ AST.PrimFCall $ AST.FCall (AST.NSimple (mkVHDLBasicId toIntegerId)) $
+ map (\exp -> Nothing AST.:=>: AST.ADExpr exp) args
+genFromSizedWord' (Right name) _ _ = error $ "\nGenerate.genFromSizedWord': Cannot generate builtin function call assigned to a VHDLName: " ++ show name
+
+
-- | Generate a generate statement for the builtin function "map"
genMap :: BuiltinBuilder
genMap (Left res) f [Left mapped_f, Left (Var arg)] =
if length args == arg_count then
builder dst f args
else
- error $ "\nGenerate.genApplication: Incorrect number of arguments to builtin function: " ++ pprString f ++ " Args: " ++ show args
- Nothing -> error $ "\nGenerate.genApplication: Using function from another module that is not a known builtin: " ++ pprString f
+ error $ "\nGenerate.genApplication(VanillaGlobal): Incorrect number of arguments to builtin function: " ++ pprString f ++ " Args: " ++ show args
+ Nothing -> error $ "\nGenerate.genApplication(VanillaGlobal): Using function from another module that is not a known builtin: " ++ pprString f
IdInfo.NotGlobalId -> do
signatures <- getA vsSignatures
-- This is a local id, so it should be a function whose definition we
portmaps = mkAssocElems (map (either exprToVHDLExpr id) args) ((either varToVHDLName id) dst) signature
in
return [mkComponentInst label entity_id portmaps]
+ IdInfo.ClassOpId cls -> do
+ -- FIXME: Not looking for what instance this class op is called for
+ -- Is quite stupid of course.
+ case (Map.lookup (varToString f) globalNameTable) of
+ Just (arg_count, builder) ->
+ if length args == arg_count then
+ builder dst f args
+ else
+ error $ "\nGenerate.genApplication(ClassOpId): Incorrect number of arguments to builtin function: " ++ pprString f ++ " Args: " ++ show args
+ Nothing -> error $ "\nGenerate.genApplication(ClassOpId): Using function from another module that is not a known builtin: " ++ pprString f
details -> error $ "\nGenerate.genApplication: Calling unsupported function " ++ pprString f ++ " with GlobalIdDetails " ++ pprString details
-----------------------------------------------------------------------------
, (hwandId , (2, genOperator2 AST.And ) )
, (hworId , (2, genOperator2 AST.Or ) )
, (hwnotId , (1, genOperator1 AST.Not ) )
+ , (plusId , (2, genOperator2 (AST.:+:) ) )
+ , (timesId , (2, genOperator2 (AST.:*:) ) )
+ , (negateId , (1, genOperator1 AST.Not ) )
+ , (minusId , (2, genOperator2 (AST.:-:) ) )
+ , (fromSizedWordId , (1, genFromSizedWord ) )
]
let name = Name.getOccString (TyCon.tyConName tycon)
case name of
"TFVec" -> mk_vector_ty ty
- -- "SizedWord" -> do
- -- res <- mk_vector_ty (sized_word_len ty) ty
- -- return $ Just $ (Arrow.second Left) res
+ "SizedWord" -> mk_unsigned_ty ty
"RangedWord" -> mk_natural_ty 0 (ranged_word_bound ty)
-- Create a custom type from this tycon
otherwise -> mk_tycon_ty tycon args
let ty_def = AST.SubtypeIn naturalTM (Just range)
return (Right (ty_id, Right ty_def))
+mk_unsigned_ty ::
+ Type.Type -- ^ Haskell type of the signed integer
+ -> TypeSession (Either String (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
+mk_unsigned_ty ty = do
+ let size = sized_word_len ty
+ let ty_id = mkVHDLExtId $ "unsigned_" ++ show (size - 1)
+ let range = AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (size - 1))]
+ let ty_def = AST.SubtypeIn signedTM (Just range)
+ return (Right (ty_id, Right ty_def))
+
-- Finds the field labels for VHDL type generated for the given Core type,
-- which must result in a record type.
getFieldLabels :: Type.Type -> TypeSession [AST.VHDLId]
Left err -> return $ Left $
"VHDLTools.mkHType: Can not construct vectortype for elementtype: " ++ pprString el_ty ++ "\n"
++ err
+ "SizedWord" -> return $ Right $ StdType $ OrdType ty
+ "RangedWord" -> return $ Right $ StdType $ OrdType ty
otherwise -> do
mkTyConHType tycon args
Nothing -> return $ Right $ StdType $ OrdType ty