Commit 50a6966a by Zachary Snow

fix three typeof conversion issues

- type of strings are left implicit
- type of implicitly-typed params uses the type of the default value
- prevent exponential blowup for large ternary expressions
parent 67466eaa
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......@@ -9,6 +10,7 @@ module Convert.TypeOf (convert) where
import Data.Tuple (swap)
import qualified Data.Map.Strict as Map
import Convert.ExprUtils (simplify)
import Convert.Scoper
import Convert.Traverse
import Language.SystemVerilog.AST
......@@ -17,21 +19,28 @@ convert :: [AST] -> [AST]
convert = map $ traverseDescriptions $ partScoper
traverseDeclM traverseModuleItemM traverseGenItemM traverseStmtM
pattern UnknownType :: Type
pattern UnknownType = Implicit Unspecified []
traverseDeclM :: Decl -> Scoper Type Decl
traverseDeclM decl = do
item <- traverseModuleItemM (MIPackageItem $ Decl decl)
let MIPackageItem (Decl decl') = item
case decl' of
Variable Local UnknownType ident [] Nil -> do
-- functions with no return type implicitly return a single bit
insertElem ident $ IntegerVector TLogic Unspecified []
return decl'
Variable d t ident a e -> do
let t' = injectRanges t a
insertElem ident t'
return $ case t' of
UnpackedType t'' a' -> Variable d t'' ident a' e
_ -> Variable d t' ident [] e
Param _ t ident _ -> do
let t' = if t == Implicit Unspecified []
then IntegerAtom TInteger Unspecified
else t
Param _ t ident e -> do
t' <- if t == UnknownType
then typeof e
else return t
insertElem ident t'
return decl'
ParamType{} -> return decl'
......@@ -63,9 +72,6 @@ lookupTypeOf expr = do
details <- lookupElemM expr
case details of
Nothing -> return $ TypeOf expr
-- functions with no return type implicitly return a single bit
Just (_, _, Implicit Unspecified []) ->
return $ IntegerVector TLogic Unspecified []
Just (_, replacements, typ) ->
return $ if Map.null replacements
then typ
......@@ -144,24 +150,30 @@ typeof (Mux _ a b) = return $ largerSizeType a b
typeof (Concat exprs) = return $ typeOfSize $ concatSize exprs
typeof (Repeat reps exprs) = return $ typeOfSize size
where size = BinOp Mul reps (concatSize exprs)
typeof String{} = return UnknownType
typeof other = lookupTypeOf other
-- produces a type large enough to hold either expression
largerSizeType :: Expr -> Expr -> Type
largerSizeType a b =
typeOfSize larger
where
sizeof = DimsFn FnBits . Right
cond = BinOp Ge (sizeof a) (sizeof b)
larger = Mux cond (sizeof a) (sizeof b)
largerSizeType a b = typeOfSize $ largerSizeOf a b
-- returns the total size of concatenated list of expressions
concatSize :: [Expr] -> Expr
concatSize exprs =
foldl (BinOp Add) (RawNum 0) $
map sizeof exprs
where
sizeof = DimsFn FnBits . Right
-- returns the size of an expression, with the short-circuiting
sizeof :: Expr -> Expr
sizeof (Number n) = RawNum $ numberBitLength n
sizeof (Mux _ a b) = largerSizeOf a b
sizeof expr = DimsFn FnBits $ Left $ TypeOf expr
-- returns the maximum size of the two given expressions
largerSizeOf :: Expr -> Expr -> Expr
largerSizeOf a b =
simplify $ Mux cond (sizeof a) (sizeof b)
where cond = BinOp Ge (sizeof a) (sizeof b)
-- produces a generic type of the given size
typeOfSize :: Expr -> Type
......
module top;
parameter SVO_MODE = "768x576";
`include "large_mux.vh"
type(SVO_HOR_PIXELS) DOUBLE_SVO_HOR_PIXELS = 2 * SVO_HOR_PIXELS;
initial begin
$display("%s", SVO_MODE);
$display("%d", SVO_HOR_PIXELS);
$display("%d", DOUBLE_SVO_HOR_PIXELS);
end
endmodule
module top;
parameter SVO_MODE = "768x576";
`include "large_mux.vh"
wire [31:0] DOUBLE_SVO_HOR_PIXELS = 2 * SVO_HOR_PIXELS;
initial begin
$display("%s", SVO_MODE);
$display("%d", SVO_HOR_PIXELS);
$display("%d", DOUBLE_SVO_HOR_PIXELS);
end
endmodule
localparam SVO_HOR_PIXELS =
SVO_MODE == "768x576" ? 768 :
SVO_MODE == "1280x854R" ? 1280 :
SVO_MODE == "2560x2048R" ? 2560 :
SVO_MODE == "1920x1200" ? 1920 :
SVO_MODE == "480x320R" ? 480 :
SVO_MODE == "1280x768R" ? 1280 :
SVO_MODE == "2560x1440R" ? 2560 :
SVO_MODE == "2048x1536" ? 2048 :
SVO_MODE == "1024x576" ? 1024 :
SVO_MODE == "320x200" ? 320 :
SVO_MODE == "384x288R" ? 384 :
SVO_MODE == "1280x1024R" ? 1280 :
SVO_MODE == "768x576R" ? 768 :
SVO_MODE == "2048x1536R" ? 2048 :
SVO_MODE == "1024x576R" ? 1024 :
SVO_MODE == "1680x1050R" ? 1680 :
SVO_MODE == "1280x854" ? 1280 :
SVO_MODE == "2560x2048" ? 2560 :
SVO_MODE == "1440x900R" ? 1440 :
SVO_MODE == "2048x1080" ? 2048 :
SVO_MODE == "1152x768R" ? 1152 :
SVO_MODE == "4096x2160" ? 4096 :
SVO_MODE == "4096x2160R" ? 4096 :
SVO_MODE == "800x480" ? 800 :
SVO_MODE == "2560x1080R" ? 2560 :
SVO_MODE == "1440x1080R" ? 1440 :
SVO_MODE == "854x480" ? 854 :
SVO_MODE == "640x480" ? 640 :
SVO_MODE == "480x320" ? 480 :
SVO_MODE == "1920x1200R" ? 1920 :
SVO_MODE == "3840x2160" ? 3840 :
SVO_MODE == "1400x1050" ? 1400 :
SVO_MODE == "854x480R" ? 854 :
SVO_MODE == "1680x1050" ? 1680 :
SVO_MODE == "320x200R" ? 320 :
SVO_MODE == "1920x1080R" ? 1920 :
SVO_MODE == "1920x1080" ? 1920 :
SVO_MODE == "2560x1440" ? 2560 :
SVO_MODE == "1440x900" ? 1440 :
SVO_MODE == "1024x600" ? 1024 :
SVO_MODE == "1400x1050R" ? 1400 :
SVO_MODE == "1366x768" ? 1366 :
SVO_MODE == "1440x1080" ? 1440 :
SVO_MODE == "1600x900" ? 1600 :
SVO_MODE == "64x48T" ? 64 :
SVO_MODE == "640x480R" ? 640 :
SVO_MODE == "352x288R" ? 352 :
SVO_MODE == "1024x768" ? 1024 :
SVO_MODE == "800x600" ? 800 :
SVO_MODE == "1280x960" ? 1280 :
SVO_MODE == "1024x768R" ? 1024 :
SVO_MODE == "1280x960R" ? 1280 :
SVO_MODE == "1600x900R" ? 1600 :
SVO_MODE == "800x600R" ? 800 :
SVO_MODE == "1280x800" ? 1280 :
SVO_MODE == "384x288" ? 384 :
SVO_MODE == "352x288" ? 352 :
SVO_MODE == "800x480R" ? 800 :
SVO_MODE == "1440x960" ? 1440 :
SVO_MODE == "3840x2160R" ? 3840 :
SVO_MODE == "2048x1080R" ? 2048 :
SVO_MODE == "1280x800R" ? 1280 :
SVO_MODE == "1366x768R" ? 1366 :
SVO_MODE == "1600x1200R" ? 1600 :
SVO_MODE == "2560x1600" ? 2560 :
SVO_MODE == "1600x1200" ? 1600 :
SVO_MODE == "320x240" ? 320 :
SVO_MODE == "1152x864" ? 1152 :
SVO_MODE == "1440x960R" ? 1440 :
SVO_MODE == "2560x1080" ? 2560 :
SVO_MODE == "1152x768" ? 1152 :
SVO_MODE == "1280x720" ? 1280 :
SVO_MODE == "1152x864R" ? 1152 :
SVO_MODE == "1024x600R" ? 1024 :
SVO_MODE == "1280x1024" ? 1280 :
SVO_MODE == "1280x768" ? 1280 :
SVO_MODE == "1280x720R" ? 1280 :
SVO_MODE == "2560x1600R" ? 2560 :
SVO_MODE == "320x240R" ? 320 :
'bx;
module top;
parameter FOO = "some useful string";
localparam type T = type(FOO);
localparam T BAR = "some other useful string";
initial $display("'%s' '%s'", FOO, BAR);
endmodule
module top;
parameter FOO = "some useful string";
localparam BAR = "some other useful string";
initial $display("'%s' '%s'", FOO, BAR);
endmodule
......@@ -70,4 +70,15 @@ module top;
$display("%b %d %d %d", i, i, $left(i), $right(i));
$display("%b %d %d %d", a, a, $left(a), $right(a));
end
localparam X = 5'b10110;
localparam Y = X + 6'b00001;
initial begin
type(X) tX = X;
type(Y) tY = Y;
$display("%b %d %d %d", X, X, $left(X), $right(X));
$display("%b %d %d %d", Y, Y, $left(Y), $right(Y));
$display("%b %d %d %d", tX, tX, $left(tX), $right(tX));
$display("%b %d %d %d", tY, tY, $left(tY), $right(tY));
end
endmodule
......@@ -85,4 +85,17 @@ module top;
$display("%b %d %d %d", a, a, 31, 0);
end
endgenerate
localparam X = 5'b10110;
localparam Y = X + 6'b00001;
initial begin : block5
reg [4:0] tX;
reg [5:0] tY;
tX = X;
tY = Y;
$display("%b %d %d %d", X, X, 4, 0);
$display("%b %d %d %d", Y, Y, 5, 0);
$display("%b %d %d %d", tX, tX, 4, 0);
$display("%b %d %d %d", tY, tY, 5, 0);
end
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