Commit ba4cf805 by Zachary Snow

preliminary conversion for size casts

parent df3620d3
...@@ -32,6 +32,7 @@ import qualified Convert.ParamType ...@@ -32,6 +32,7 @@ import qualified Convert.ParamType
import qualified Convert.RemoveComments import qualified Convert.RemoveComments
import qualified Convert.Return import qualified Convert.Return
import qualified Convert.Simplify import qualified Convert.Simplify
import qualified Convert.SizeCast
import qualified Convert.StarPort import qualified Convert.StarPort
import qualified Convert.StmtBlock import qualified Convert.StmtBlock
import qualified Convert.Stream import qualified Convert.Stream
...@@ -58,6 +59,7 @@ phases excludes = ...@@ -58,6 +59,7 @@ phases excludes =
, Convert.PackedArray.convert , Convert.PackedArray.convert
, Convert.DimensionQuery.convert , Convert.DimensionQuery.convert
, Convert.ParamType.convert , Convert.ParamType.convert
, Convert.SizeCast.convert
, Convert.Simplify.convert , Convert.Simplify.convert
, Convert.StarPort.convert , Convert.StarPort.convert
, Convert.StmtBlock.convert , Convert.StmtBlock.convert
......
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
- Conversion of size casts on non-constant expressions.
-}
module Convert.SizeCast (convert) where
import Control.Monad.State
import Control.Monad.Writer
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Convert.Traverse
import Language.SystemVerilog.AST
type TypeMap = Map.Map Identifier Type
type CastSet = Set.Set (Int, Signing)
type ST = StateT TypeMap (Writer CastSet)
convert :: [AST] -> [AST]
convert = map convertFile
convertFile :: AST -> AST
convertFile descriptions =
descriptions' ++ map (uncurry castFn) funcs
where
results = map convertDescription descriptions
descriptions' = map fst results
funcs = Set.toList $ Set.unions $ map snd results
convertDescription :: Description -> (Description, CastSet)
convertDescription description =
(description', info)
where
(description', info) =
runWriter $
scopedConversionM traverseDeclM traverseModuleItemM traverseStmtM
Map.empty description
traverseDeclM :: Decl -> ST Decl
traverseDeclM decl = do
case decl of
Variable _ t x _ _ -> modify $ Map.insert x t
Param _ t x _ -> modify $ Map.insert x t
ParamType _ _ _ -> return ()
return decl
traverseModuleItemM :: ModuleItem -> ST ModuleItem
traverseModuleItemM item = traverseExprsM traverseExprM item
traverseStmtM :: Stmt -> ST Stmt
traverseStmtM stmt = traverseStmtExprsM traverseExprM stmt
traverseExprM :: Expr -> ST Expr
traverseExprM =
traverseNestedExprsM convertExprM
where
convertExprM :: Expr -> ST Expr
convertExprM (Cast (Right (Number n)) e) = do
typeMap <- get
case (readNumber n, exprSigning typeMap e) of
(Just size, Just sg) -> do
lift $ tell $ Set.singleton (size, sg)
let f = castFnName size sg
let args = Args [Just e] []
return $ Call Nothing f args
_ -> return $ Cast (Right $ Number n) e
convertExprM other = return other
castFn :: Int -> Signing -> Description
castFn n sg =
PackageItem $
Function (Just Automatic) t fnName [decl] [Return $ Ident inp]
where
inp = "inp"
r = (Number $ show (n - 1), Number "0")
t = IntegerVector TLogic sg [r]
fnName = castFnName n sg
decl = Variable Input t inp [] Nothing
castFnName :: Int -> Signing -> String
castFnName n sg =
if n <= 0
then error $ "cannot have non-positive size cast: " ++ show n
else
if sg == Unspecified
then init name
else name
where name = "sv2v_cast_" ++ show n ++ "_" ++ show sg
exprSigning :: TypeMap -> Expr -> Maybe Signing
exprSigning typeMap (Ident x) =
case Map.lookup x typeMap of
Just t -> typeSigning t
Nothing -> Just Unspecified
exprSigning typeMap (BinOp op e1 e2) =
combiner sg1 sg2
where
sg1 = exprSigning typeMap e1
sg2 = exprSigning typeMap e2
combiner = case op of
BitAnd -> combineSigning
BitXor -> combineSigning
BitXnor -> combineSigning
BitOr -> combineSigning
Mul -> combineSigning
Div -> combineSigning
Add -> combineSigning
Sub -> combineSigning
Mod -> curry fst
Pow -> curry fst
ShiftAL -> curry fst
ShiftAR -> curry fst
_ -> \_ _ -> Just Unspecified
exprSigning _ _ = Just Unspecified
combineSigning :: Maybe Signing -> Maybe Signing -> Maybe Signing
combineSigning Nothing _ = Nothing
combineSigning _ Nothing = Nothing
combineSigning (Just Unspecified) msg = msg
combineSigning msg (Just Unspecified) = msg
combineSigning (Just Signed) _ = Just Signed
combineSigning _ (Just Signed) = Just Signed
combineSigning (Just Unsigned) _ = Just Unsigned
typeSigning :: Type -> Maybe Signing
typeSigning (Net _ sg _) = Just sg
typeSigning (Implicit sg _) = Just sg
typeSigning (IntegerVector _ sg _) = Just sg
typeSigning _ = Nothing
...@@ -78,11 +78,13 @@ module Convert.Traverse ...@@ -78,11 +78,13 @@ module Convert.Traverse
, collectNestedLHSsM , collectNestedLHSsM
, traverseScopesM , traverseScopesM
, scopedConversion , scopedConversion
, scopedConversionM
, stately , stately
, traverseFilesM , traverseFilesM
, traverseFiles , traverseFiles
) where ) where
import Data.Functor.Identity (runIdentity)
import Control.Monad.State import Control.Monad.State
import Control.Monad.Writer import Control.Monad.Writer
import Language.SystemVerilog.AST import Language.SystemVerilog.AST
...@@ -1009,10 +1011,11 @@ collectNestedExprsM = collectify traverseNestedExprsM ...@@ -1009,10 +1011,11 @@ collectNestedExprsM = collectify traverseNestedExprsM
-- statements recursively, as we add a recursive wrapper here. -- statements recursively, as we add a recursive wrapper here.
traverseScopesM traverseScopesM
:: (Eq s, Show s) :: (Eq s, Show s)
=> MapperM (State s) Decl => Monad m
-> MapperM (State s) ModuleItem => MapperM (StateT s m) Decl
-> MapperM (State s) Stmt -> MapperM (StateT s m) ModuleItem
-> MapperM (State s) ModuleItem -> MapperM (StateT s m) Stmt
-> MapperM (StateT s m) ModuleItem
traverseScopesM declMapper moduleItemMapper stmtMapper = traverseScopesM declMapper moduleItemMapper stmtMapper =
fullModuleItemMapper fullModuleItemMapper
where where
...@@ -1072,7 +1075,19 @@ scopedConversion ...@@ -1072,7 +1075,19 @@ scopedConversion
-> Description -> Description
-> Description -> Description
scopedConversion traverseDeclM traverseModuleItemM traverseStmtM s description = scopedConversion traverseDeclM traverseModuleItemM traverseStmtM s description =
evalState (initialTraverse description >>= scopedTraverse) s runIdentity $ scopedConversionM traverseDeclM traverseModuleItemM traverseStmtM s description
scopedConversionM
:: (Eq s, Show s)
=> Monad m
=> MapperM (StateT s m) Decl
-> MapperM (StateT s m) ModuleItem
-> MapperM (StateT s m) Stmt
-> s
-> Description
-> m Description
scopedConversionM traverseDeclM traverseModuleItemM traverseStmtM s description =
evalStateT (initialTraverse description >>= scopedTraverse) s
where where
initialTraverse = traverseModuleItemsM traverseMIPackageItemDecl initialTraverse = traverseModuleItemsM traverseMIPackageItemDecl
scopedTraverse = traverseModuleItemsM $ scopedTraverse = traverseModuleItemsM $
......
...@@ -77,6 +77,7 @@ executable sv2v ...@@ -77,6 +77,7 @@ executable sv2v
Convert.RemoveComments Convert.RemoveComments
Convert.Return Convert.Return
Convert.Simplify Convert.Simplify
Convert.SizeCast
Convert.StarPort Convert.StarPort
Convert.StmtBlock Convert.StmtBlock
Convert.Stream Convert.Stream
......
module top;
initial begin
logic [31:0] w = 1234;
int x = -235;
int y = 1234;
logic [4:0] z = y;
$display("%0d %0d", w, 5'(w));
$display("%0d %0d", x, 5'(x));
$display("%0d %0d", y, 5'(y));
$display("%0d %0d", z, 5'(z));
$display("%0d %0d", w+1, 5'(w+1));
$display("%0d %0d", x+1, 5'(x+1));
$display("%0d %0d", y+1, 5'(y+1));
$display("%0d %0d", z+1, 5'(z+1));
$display("%b %b", w, 40'(w));
$display("%b %b", x, 40'(x));
$display("%b %b", y, 40'(y));
$display("%b %b", z, 40'(z));
end
localparam bit foo = '0;
localparam logic [31:0] bar = 32'(foo);
initial $display("%b %b", foo, bar);
endmodule
module top;
initial begin : foo_block
reg [31:0] w;
reg signed [31:0] x;
reg signed [31:0] y;
reg [4:0] z;
w = 1234;
x = -235;
y = 1234;
z = y;
$display("%0d %0d", w, w[4:0]);
$display("%0d %0d", x, $signed(x[4:0]));
$display("%0d %0d", y, $signed(y[4:0]));
$display("%0d %0d", z, z[4:0]);
$display("%0d %0d", w+1, w[4:0]+1);
$display("%0d %0d", x+1, $signed(x[4:0])+1);
$display("%0d %0d", y+1, $signed(y[4:0])+1);
$display("%0d %0d", z+1, z[4:0]+1);
$display("%b %b", w, {8'b0, w});
$display("%b %b", x, {8'hFF, x});
$display("%b %b", y, {8'b0, y});
$display("%b %b", z, {35'b0, z});
end
localparam foo = 0;
localparam [31:0] bar = 32'b0;
initial $display("%b %b", foo, bar);
endmodule
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment