Commit 2a2d819b by Zachary Snow

additional codegen test coverage

- assertions, gen case, and inout
- simplify block codegen
- remove blank lines in tasks with no inputs
parent 2311d3e2
......@@ -13,7 +13,6 @@ module Language.SystemVerilog.AST.Description
) where
import Data.Maybe (fromMaybe)
import Data.List (intercalate)
import Text.Printf (printf)
import Language.SystemVerilog.AST.ShowHelp
......@@ -31,7 +30,7 @@ data Description
deriving Eq
instance Show Description where
showList descriptions _ = intercalate "\n" $ map show descriptions
showList l _ = unlines' $ map show l
show (Part attrs True kw lifetime name _ items) =
printf "%sextern %s %s%s %s;"
(concatMap showPad attrs)
......@@ -66,13 +65,11 @@ data PackageItem
instance Show PackageItem where
show (Typedef t x) = printf "typedef %s %s;" (show t) x
show (Function ml t x i b) =
printf "function %s%s%s;\n%s\n%s\nendfunction"
(showPad ml) (showPad t) x (indent $ show i)
(indent $ unlines' $ map show b)
printf "function %s%s%s;\n%s\nendfunction" (showPad ml) (showPad t) x
(showBlock i b)
show (Task ml x i b) =
printf "task %s%s;\n%s\n%s\nendtask"
(showPad ml) x (indent $ show i)
(indent $ unlines' $ map show b)
printf "task %s%s;\n%s\nendtask"
(showPad ml) x (showBlock i b)
show (Import x y) = printf "import %s::%s;" x (fromMaybe "*" y)
show (Export Nothing) = "export *::*";
show (Export (Just (x, y))) = printf "export %s::%s;" x (fromMaybe "*" y)
......
......@@ -33,7 +33,7 @@ instance Show GenItem where
show (GenBlock x i) =
printf "begin%s\n%s\nend"
(if null x then "" else " : " ++ x)
(indent $ unlines' $ map show i)
(indent $ show i)
show (GenCase e cs) =
printf "case (%s)\n%s\nendcase" (show e) bodyStr
where bodyStr = indent $ unlines' $ map showGenCase cs
......
......@@ -54,7 +54,7 @@ instance Show ModuleItem where
show (Assign o a b) = printf "assign %s%s = %s;" (showPad o) (show a) (show b)
show (Defparam a b) = printf "defparam %s = %s;" (show a) (show b)
show (Genvar x ) = printf "genvar %s;" x
show (Generate b ) = printf "generate\n%s\nendgenerate" (indent $ unlines' $ map show b)
show (Generate b ) = printf "generate\n%s\nendgenerate" (indent $ show b)
show (Modport x l) = printf "modport %s(\n%s\n);" x (indent $ intercalate ",\n" $ map showModportDecl l)
show (Initial s ) = printf "initial %s" (show s)
show (Final s ) = printf "final %s" (show s)
......
......@@ -13,6 +13,7 @@ module Language.SystemVerilog.AST.ShowHelp
, commas
, indentedParenList
, showEither
, showBlock
) where
import Data.List (intercalate)
......@@ -52,3 +53,8 @@ indentedParenList l = "(\n" ++ (indent $ intercalate ",\n" l) ++ "\n)"
showEither :: (Show a, Show b) => Either a b -> String
showEither (Left v) = show v
showEither (Right v) = show v
showBlock :: (Show a, Show b) => [a] -> [b] -> String
showBlock a [] = indent $ show a
showBlock [] b = indent $ show b
showBlock a b = indent $ show a ++ "\n" ++ show b
......@@ -25,7 +25,7 @@ module Language.SystemVerilog.AST.Stmt
import Text.Printf (printf)
import Language.SystemVerilog.AST.ShowHelp (commas, indent, unlines', showPad)
import Language.SystemVerilog.AST.ShowHelp (commas, indent, unlines', showPad, showBlock)
import Language.SystemVerilog.AST.Attr (Attr)
import Language.SystemVerilog.AST.Decl (Decl)
import Language.SystemVerilog.AST.Expr (Expr(Inside, Nil), Args(..), showExprOrRange)
......@@ -57,13 +57,13 @@ data Stmt
deriving Eq
instance Show Stmt where
showList l _ = unlines' $ map show l
show (StmtAttr attr stmt) = printf "%s\n%s" (show attr) (show stmt)
show (Block kw name decls stmts) =
printf "%s%s\n%s\n%s" (show kw) header body (blockEndToken kw)
where
header = if null name then "" else " : " ++ name
bodyLines = (map show decls) ++ (map show stmts)
body = indent $ unlines' bodyLines
body = showBlock decls stmts
show (Case u kw e cs) =
printf "%s%s (%s)\n%s\nendcase" (showPad u) (show kw) (show e) bodyStr
where bodyStr = indent $ unlines' $ map showCase cs
......@@ -104,9 +104,8 @@ instance Show Stmt where
else "// " ++ c
showBranch :: Stmt -> String
showBranch (Block Seq "" [] [CommentStmt c, stmt]) =
'\n' : (indent $ unlines' $ map show stmts)
where stmts = [CommentStmt c, stmt]
showBranch (Block Seq "" [] (stmts @ [CommentStmt{}, _])) =
'\n' : (indent $ show stmts)
showBranch (block @ Block{}) = ' ' : show block
showBranch stmt = '\n' : (indent $ show stmt)
......
module Module(input clock, input clear, input data);
logic x, y;
assign y = data;
assign x = y;
assert property (
@(posedge clock) disable iff(clear) x == y
);
task hello;
$display("Hello!");
assert property (x == y);
endtask
endmodule
module Module(input clock, input clear, input data);
wire x, y;
assign y = data;
assign x = y;
task hello;
$display("Hello!");
endtask
endmodule
module top;
reg clock;
initial begin
clock = 0;
repeat (100)
#1 clock = ~clock;
end
reg clear;
initial clear = 0;
reg data;
initial data = 0;
Module m(clock, clear, data);
initial m.hello;
endmodule
module top;
task t;
input x;
begin : y
reg z;
end
endtask
initial t(0);
endmodule
module Module;
parameter X = 1;
case (X)
1: initial $display("A");
2: initial $display("B");
default: initial $display("C");
3: ;
endcase
endmodule
module top;
Module #(1) a();
Module #(2) b();
Module #(3) c();
Module #(4) d();
endmodule
module Module(x, y);
inout x, y;
parameter DIR = 1;
if (DIR)
assign x = y;
else
assign y = x;
endmodule
module top;
wire inp = 1;
wire out1, out2;
Module #(0) fwd(inp, out1);
Module #(1) rev(out2, inp);
initial $display("%b %b %b", inp, out1, out2);
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