Commit 95208947 by Zachary Snow

unbased unsized conversion refactor

- support ubased unsized bound to ports using injected constants
- explicit context-aware literal sizing for complex expressions
- fix infinite loop case in NestPI conversion
- elaborate size-casts of converted literals
parent 1903bc19
......@@ -68,7 +68,7 @@ addItems pis existingPIs (item : items) =
, collectTypesM $ collectNestedTypesM collectTypenamesM
, collectExprsM $ collectNestedExprsM collectIdentsM
]
neededPIs = Set.difference usedPIs existingPIs
neededPIs = Set.difference (Set.difference usedPIs existingPIs) thisPI
itemsToAdd = map MIPackageItem $ Map.elems $
Map.restrictKeys pis neededPIs
addItems _ _ [] = []
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......@@ -54,6 +55,9 @@ traverseModuleItemM item = traverseExprsM traverseExprM item
traverseStmtM :: Stmt -> ST Stmt
traverseStmtM stmt = traverseStmtExprsM traverseExprM stmt
pattern ConvertedUU :: Char -> Expr
pattern ConvertedUU ch = Number ['1', '\'', 's', 'b', ch]
traverseExprM :: Expr -> ST Expr
traverseExprM =
traverseNestedExprsM convertExprM
......@@ -85,6 +89,13 @@ traverseExprM =
convertExprM other = return other
convertCastM :: Expr -> Expr -> ST Expr
convertCastM (s @ (Number str)) (e @ (ConvertedUU ch)) = do
typeMap <- get
case (exprSigning typeMap e, readNumber str) of
(Just Unspecified, Just n) -> return $ Number $
show n ++ "'b" ++ take (fromIntegral n) (repeat ch)
(Just sg, _) -> convertCastWithSigningM s e sg
_ -> return $ Cast (Right s) e
convertCastM s e = do
typeMap <- get
case exprSigning typeMap e of
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
- Conversion for unbased, unsized literals ('0, '1, 'z, 'x)
-
- The literals are given a binary base and are made signed to allow sign
- extension. This enables the desired implicit casting in Verilog-2005.
- However, in self-determined contextes, the literals are given an explicit
- size of 1.
- The literals are given a binary base, a size of 1, and are made signed to
- allow sign extension. For context-determined expressions, the converted
- literals are explicitly cast to the appropriate context-determined size.
-
- As a special case, unbased, unsized literals which take on the size of a
- module port binding are replaced with a hierarchical reference to an
- appropriately sized constant which is injected into the instantiated module's
- definition. This allows these literals to be used for parameterized ports
- without further complicating other conversions, as hierarchical references
- are not allowed within constant expressions.
-}
module Convert.UnbasedUnsized (convert) where
import Control.Monad.Writer
import Convert.Traverse
import Language.SystemVerilog.AST
data ExprContext
= SelfDetermined
| ContextDetermined Expr
deriving (Eq, Show)
type Port = Either Identifier Int
data Bind = Bind
{ bModule :: Identifier
, bBit :: Char
, bPort :: Port
} deriving (Eq, Show)
type Binds = [Bind]
convert :: [AST] -> [AST]
convert = map $ traverseDescriptions $ traverseModuleItems convertModuleItem
convert files =
map (traverseDescriptions $ convertDescription binds) files'
where
(files', binds) = runWriter $
mapM (mapM $ traverseModuleItemsM convertModuleItemM) files
convertDescription :: Binds -> Description -> Description
convertDescription [] other = other
convertDescription binds (Part attrs extern kw lifetime name ports items) =
Part attrs extern kw lifetime name ports items'
where
binds' = filter ((== name) . bModule) binds
items' = removeDupes [] $ items ++ map (bindItem ports) binds'
removeDupes :: [Identifier] -> [ModuleItem] -> [ModuleItem]
removeDupes _ [] = []
removeDupes existing (item @ (MIPackageItem (Decl decl)) : is) =
case decl of
Param Localparam _ x _ ->
if elem x existing
then removeDupes existing is
else item : removeDupes (x : existing) is
_ -> item : removeDupes existing is
removeDupes existing (item : is) =
item : removeDupes existing is
convertDescription _ other = other
bindName :: Bind -> Identifier
bindName (Bind _ ch (Left x)) = "sv2v_uub_" ++ ch : '_' : x
bindName (Bind m ch (Right i)) =
bindName $ Bind m ch (Left $ show i)
bindItem :: [Identifier] -> Bind -> ModuleItem
bindItem ports bind =
MIPackageItem $ Decl $ Param Localparam typ name expr
where
portName = lookupPort ports (bPort bind)
size = DimsFn FnBits $ Right $ Ident portName
rng = (BinOp Sub size (Number "1"), Number "0")
typ = Implicit Unspecified [rng]
name = bindName bind
expr = literalFor $ bBit bind
lookupPort :: [Identifier] -> Port -> Identifier
lookupPort _ (Left x) = x
lookupPort ports (Right i) =
if i < length ports
then ports !! i
else error $ "out of bounds bort binding " ++ show (ports, i)
convertModuleItemM :: ModuleItem -> Writer Binds ModuleItem
convertModuleItemM (Instance moduleName params instanceName [] bindings) = do
bindings' <- mapM (uncurry convertBinding) $ zip bindings [0..]
let item = Instance moduleName params instanceName [] bindings'
return $ convertModuleItem item
where
tag = Ident ":uub:"
convertBinding :: PortBinding -> Int -> Writer Binds PortBinding
convertBinding (portName, expr) idx = do
let port = if null portName then Right idx else Left portName
let expr' = convertExpr (ContextDetermined tag) expr
expr'' <- traverseNestedExprsM (replaceBindingExpr port) expr'
return (portName, expr'')
replaceBindingExpr :: Port -> Expr -> Writer Binds Expr
replaceBindingExpr port (orig @ (Cast Right{} (Number num))) = do
let ch = last num
if orig == sizedLiteralFor tag ch
then do
let bind = Bind moduleName ch port
tell [bind]
let expr = Dot (Ident instanceName) (bindName bind)
return expr
else return orig
replaceBindingExpr _ other = return other
convertModuleItemM other = return $ convertModuleItem other
convertModuleItem :: ModuleItem -> ModuleItem
convertModuleItem =
traverseExprs (traverseNestedExprs convertExpr) .
traverseStmts (traverseNestedStmts convertStmt) .
traverseTypes (traverseNestedTypes convertType)
traverseExprs (convertExpr SelfDetermined) .
traverseTypes (traverseNestedTypes convertType) .
traverseAsgns convertAsgn
digits :: [Char]
digits = ['0', '1', 'x', 'z', 'X', 'Z']
literalFor :: String -> Char -> Expr
literalFor prefix ch =
literalFor :: Char -> Expr
literalFor ch =
if elem ch digits
then Number (prefix ++ [ch])
then Number ("1'sb" ++ [ch])
else error $ "unexpected unbased-unsized digit: " ++ [ch]
sizedLiteralFor :: Char -> Expr
sizedLiteralFor = literalFor "1'sb"
unsizedLiteralFor :: Char -> Expr
unsizedLiteralFor '1' = UniOp UniSub $ Number "'sd1"
unsizedLiteralFor ch = literalFor "'sd" ch
convertExpr :: Expr -> Expr
convertExpr (DimsFn fn (Right e)) =
DimsFn fn $ Right $ convertSizeExpr e
convertExpr (Concat exprs) =
Concat $ map convertSelfDeterminedExpr exprs
convertExpr (Repeat count exprs) =
Repeat count $ map convertSelfDeterminedExpr exprs
convertExpr (Number ['\'', ch]) =
unsizedLiteralFor ch
convertExpr other = other
convertSelfDeterminedExpr :: Expr -> Expr
convertSelfDeterminedExpr (Number ['\'', ch]) =
sizedLiteralFor ch
convertSelfDeterminedExpr other = other
convertStmt :: Stmt -> Stmt
convertStmt (Subroutine (fn @ (Ident ('$' : _))) (Args args [])) =
Subroutine fn (Args args' [])
where args' = map convertSelfDeterminedExpr args
convertStmt other = other
sizedLiteralFor :: Expr -> Char -> Expr
sizedLiteralFor expr ch =
Cast (Right size) (literalFor ch)
where size = DimsFn FnBits $ Right expr
convertAsgn :: (LHS, Expr) -> (LHS, Expr)
convertAsgn (lhs, expr) =
(lhs, convertExpr context expr)
where context = ContextDetermined $ lhsToExpr lhs
convertExpr :: ExprContext -> Expr -> Expr
convertExpr _ (DimsFn fn (Right e)) =
DimsFn fn $ Right $ convertExpr SelfDetermined e
convertExpr _ (Cast te e) =
Cast te $ convertExpr SelfDetermined e
convertExpr _ (Concat exprs) =
Concat $ map (convertExpr SelfDetermined) exprs
convertExpr _ (Pattern items) =
Pattern $ zip
(map fst items)
(map (convertExpr SelfDetermined . snd) items)
convertExpr _ (Call expr (Args pnArgs kwArgs)) =
Call expr $ Args pnArgs' kwArgs'
where
pnArgs' = map (convertExpr SelfDetermined) pnArgs
Pattern kwArgs' = convertExpr SelfDetermined $ Pattern kwArgs
convertExpr _ (Repeat count exprs) =
Repeat count $ map (convertExpr SelfDetermined) exprs
convertExpr SelfDetermined (Mux cond (e1 @ UU{}) (e2 @ UU{})) =
Mux
(convertExpr SelfDetermined cond)
(convertExpr SelfDetermined e1)
(convertExpr SelfDetermined e2)
convertExpr SelfDetermined (Mux cond e1 e2) =
Mux
(convertExpr SelfDetermined cond)
(convertExpr (ContextDetermined e2) e1)
(convertExpr (ContextDetermined e1) e2)
convertExpr (ContextDetermined expr) (Mux cond e1 e2) =
Mux
(convertExpr SelfDetermined cond)
(convertExpr context e1)
(convertExpr context e2)
where context = ContextDetermined expr
convertExpr SelfDetermined (BinOp op e1 e2) =
if isPeerSizedBinOp op || isParentSizedBinOp op
then BinOp op
(convertExpr (ContextDetermined e2) e1)
(convertExpr (ContextDetermined e1) e2)
else BinOp op
(convertExpr SelfDetermined e1)
(convertExpr SelfDetermined e2)
convertExpr (ContextDetermined expr) (BinOp op e1 e2) =
if isPeerSizedBinOp op then
BinOp op
(convertExpr (ContextDetermined e2) e1)
(convertExpr (ContextDetermined e1) e2)
else if isParentSizedBinOp op then
BinOp op
(convertExpr context e1)
(convertExpr context e2)
else
BinOp op
(convertExpr SelfDetermined e1)
(convertExpr SelfDetermined e2)
where context = ContextDetermined expr
convertExpr context (UniOp op expr) =
if isSizedUniOp op
then UniOp op (convertExpr context expr)
else UniOp op (convertExpr SelfDetermined expr)
convertExpr SelfDetermined (UU ch) =
literalFor ch
convertExpr (ContextDetermined expr) (UU ch) =
sizedLiteralFor expr ch
convertExpr _ other = other
pattern UU :: Char -> Expr
pattern UU ch = Number ['\'', ch]
convertType :: Type -> Type
convertType (TypeOf e) = TypeOf $ convertSizeExpr e
convertType (TypeOf e) = TypeOf $ convertExpr SelfDetermined e
convertType other = other
convertSizeExpr :: Expr -> Expr
convertSizeExpr (Mux cond e1 e2) =
Mux cond e1' e2'
where
e1' = convertSelfDeterminedExpr e1
e2' = convertSelfDeterminedExpr e2
convertSizeExpr e = convertSelfDeterminedExpr e
isParentSizedBinOp :: BinOp -> Bool
isParentSizedBinOp BitAnd = True
isParentSizedBinOp BitXor = True
isParentSizedBinOp BitXnor = True
isParentSizedBinOp BitOr = True
isParentSizedBinOp Mul = True
isParentSizedBinOp Div = True
isParentSizedBinOp Mod = True
isParentSizedBinOp Add = True
isParentSizedBinOp Sub = True
isParentSizedBinOp _ = False
isPeerSizedBinOp :: BinOp -> Bool
isPeerSizedBinOp Eq = True
isPeerSizedBinOp Ne = True
isPeerSizedBinOp TEq = True
isPeerSizedBinOp TNe = True
isPeerSizedBinOp WEq = True
isPeerSizedBinOp WNe = True
isPeerSizedBinOp Lt = True
isPeerSizedBinOp Le = True
isPeerSizedBinOp Gt = True
isPeerSizedBinOp Ge = True
isPeerSizedBinOp _ = False
isSizedUniOp :: UniOp -> Bool
isSizedUniOp = (/= LogNot)
`define TEST(value) \
logic [63:0] val_``value = 'value; \
initial $display(`"'value -> %b (%0d) %b (%0d)", \
initial $display(`"'value -> %b (%0d) %b (%0d)`", \
val_``value, $bits(val_``value), \
'value, $bits('value) \
);
......@@ -46,4 +46,69 @@ module top;
$display($bits(type('1)));
$display($bits(type(flag ? '1 : 'x)));
end
parameter P = 1;
M m1('0, '1, 'x, 'z);
M #( 2) m2('0, '1, 'x, 'z);
M #(28) m3('0, '1, 'x, 'z);
M #(29) m4('0, '1, 'x, 'z);
M #(30) m5('0, '1, 'x, 'z);
M #(31) m6('0, '1, 'x, 'z);
M #(32) m7('0, '1, 'x, 'z);
M #(33) m8('0, '1, 'x, 'z);
M #(34) m9('0, '1, 'x, 'z);
M #(31) mA(P ? '0 : '1, !P ? '0 : '1, 'x, 'z);
M #(34) mB(P ? '0 : '1, !P ? '0 : '1, 'x, 'z);
M #(31) mC(P ? '0 : '0 + '1, !P ? '0 : '0 + '1, 'x, 'z);
M #(34) mD(P ? '0 : '0 + '1, !P ? '0 : '0 + '1, 'x, 'z);
`define TEST_OP(left, op, right, expected) \
$display(`"%s: (left) op (right) -> %b (ref: %b)`", \
((left) op (right)) == expected ? "PASS" : "FAIL", \
(left) op (right), expected \
);
initial begin
`TEST_OP( 1'h1 , ==, '1, 1'b1)
`TEST_OP( 2'h3 , ==, '1, 1'b1)
`TEST_OP(31'h7fffffff , ==, '1, 1'b1)
`TEST_OP(32'hffffffff , ==, '1, 1'b1)
`TEST_OP(33'h1ffffffff, ==, '1, 1'b1)
`TEST_OP( 1'h1 , <=, '1, 1'b1)
`TEST_OP( 2'h3 , <=, '1, 1'b1)
`TEST_OP(31'h7fffffff , <=, '1, 1'b1)
`TEST_OP(32'hffffffff , <=, '1, 1'b1)
`TEST_OP(33'h1ffffffff, <=, '1, 1'b1)
`TEST_OP( 1'h1 , >=, '1, 1'b1)
`TEST_OP( 2'h3 , >=, '1, 1'b1)
`TEST_OP(31'h7fffffff , >=, '1, 1'b1)
`TEST_OP(32'hffffffff , >=, '1, 1'b1)
`TEST_OP(33'h1ffffffff, >=, '1, 1'b1)
`TEST_OP( 1'h1 , &, '1, 1'h1 )
`TEST_OP( 2'h3 , &, '1, 2'h3 )
`TEST_OP(31'h7fffffff , &, '1, 31'h7fffffff )
`TEST_OP(32'hffffffff , &, '1, 32'hffffffff )
`TEST_OP(33'h1ffffffff, &, '1, 33'h1ffffffff)
`TEST_OP(33'h1ffffffff, &, P ? '1 : '0, 33'h1ffffffff)
`TEST_OP(33'h1ffffffff, &, '1 & '1, 33'h1ffffffff)
`TEST_OP(33'h1ffffffff, &, !P ? '1 : '0 - 1, 33'h1ffffffff)
`TEST_OP(34'h3ffffffff, &, '0 - 1, 34'h3ffffffff)
`TEST_OP(1, ==, 2'h3 == '1, 1'b1)
end
endmodule
module M(a, b, c, d);
parameter W = 1;
input logic [W+0:1] a;
input logic [W+1:1] b;
input logic [W+2:1] c;
input logic [W+3:1] d;
initial $display("M W=%0d %b %b %b %b", W, a, b, c, d);
endmodule
`define TEST(value) \
wire [63:0] val_``value = {64{1'b``value}}; \
initial $display(`"'value -> %b (%0d) %b (%0d)", \
initial $display(`"'value -> %b (%0d) %b (%0d)`", \
val_``value, $bits(val_``value), \
1'b``value, $bits(1'b``value) \
);
......@@ -25,7 +25,7 @@ module top;
flag = 1;
a = (flag ? 32'hFFFFFFFF : i);
b = (flag ? 32'hXXXXXXXX : i);
c = (flag ? 32'hFFFFFFFF: i);
c = (flag ? 32'hFFFFFFFF : i);
d = (flag ? 64'hFFFFFFFFFFFFFFFF : j);
e = (flag ? 64'hXXXXXXXXXXXXXXXX : j);
$display("%b", a);
......@@ -46,4 +46,64 @@ module top;
$display(1);
$display(1);
end
M m1({ 1 {1'b0}}, { 2 {1'b1}}, { 3 {1'bx}}, { 4 {1'bz}});
M #( 2) m2({ 2 {1'b0}}, { 3 {1'b1}}, { 4 {1'bx}}, { 5 {1'bz}});
M #(28) m3({28 {1'b0}}, {29 {1'b1}}, {30 {1'bx}}, {31 {1'bz}});
M #(29) m4({29 {1'b0}}, {30 {1'b1}}, {31 {1'bx}}, {32 {1'bz}});
M #(30) m5({30 {1'b0}}, {31 {1'b1}}, {32 {1'bx}}, {33 {1'bz}});
M #(31) m6({31 {1'b0}}, {32 {1'b1}}, {33 {1'bx}}, {34 {1'bz}});
M #(32) m7({32 {1'b0}}, {33 {1'b1}}, {34 {1'bx}}, {35 {1'bz}});
M #(33) m8({33 {1'b0}}, {34 {1'b1}}, {35 {1'bx}}, {36 {1'bz}});
M #(34) m9({34 {1'b0}}, {35 {1'b1}}, {36 {1'bx}}, {37 {1'bz}});
M #(31) mA({31 {1'b0}}, {32 {1'b1}}, {33 {1'bx}}, {34 {1'bz}});
M #(34) mB({34 {1'b0}}, {35 {1'b1}}, {36 {1'bx}}, {37 {1'bz}});
M #(31) mC({31 {1'b0}}, {32 {1'b1}}, {33 {1'bx}}, {34 {1'bz}});
M #(34) mD({34 {1'b0}}, {35 {1'b1}}, {36 {1'bx}}, {37 {1'bz}});
`define TEST_OP(left, op, right, expected) \
$display(`"PASS: (left) op (right) -> %b (ref: %b)`", expected, expected);
initial begin
`TEST_OP( 1'h1 , ==, '1, 1'b1)
`TEST_OP( 2'h3 , ==, '1, 1'b1)
`TEST_OP(31'h7fffffff , ==, '1, 1'b1)
`TEST_OP(32'hffffffff , ==, '1, 1'b1)
`TEST_OP(33'h1ffffffff, ==, '1, 1'b1)
`TEST_OP( 1'h1 , <=, '1, 1'b1)
`TEST_OP( 2'h3 , <=, '1, 1'b1)
`TEST_OP(31'h7fffffff , <=, '1, 1'b1)
`TEST_OP(32'hffffffff , <=, '1, 1'b1)
`TEST_OP(33'h1ffffffff, <=, '1, 1'b1)
`TEST_OP( 1'h1 , >=, '1, 1'b1)
`TEST_OP( 2'h3 , >=, '1, 1'b1)
`TEST_OP(31'h7fffffff , >=, '1, 1'b1)
`TEST_OP(32'hffffffff , >=, '1, 1'b1)
`TEST_OP(33'h1ffffffff, >=, '1, 1'b1)
`TEST_OP( 1'h1 , &, '1, 1'h1 )
`TEST_OP( 2'h3 , &, '1, 2'h3 )
`TEST_OP(31'h7fffffff , &, '1, 31'h7fffffff )
`TEST_OP(32'hffffffff , &, '1, 32'hffffffff )
`TEST_OP(33'h1ffffffff, &, '1, 33'h1ffffffff)
`TEST_OP(33'h1ffffffff, &, P ? '1 : '0, 33'h1ffffffff)
`TEST_OP(33'h1ffffffff, &, '1 & '1, 33'h1ffffffff)
`TEST_OP(33'h1ffffffff, &, !P ? '1 : '0 - 1, 33'h1ffffffff)
`TEST_OP(34'h3ffffffff, &, '0 - 1, 34'h3ffffffff)
`TEST_OP(1, ==, 2'h3 == '1, 1'b1)
end
endmodule
module M(a, b, c, d);
parameter W = 1;
input wire [W+0:1] a;
input wire [W+1:1] b;
input wire [W+2:1] c;
input wire [W+3:1] d;
initial $display("M W=%0d %b %b %b %b", W, a, b, c, d);
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