aboutsummaryrefslogtreecommitdiffstats
path: root/test/Reduce.hs
diff options
context:
space:
mode:
Diffstat (limited to 'test/Reduce.hs')
-rw-r--r--test/Reduce.hs322
1 files changed, 230 insertions, 92 deletions
diff --git a/test/Reduce.hs b/test/Reduce.hs
index afd5e0a..85a0654 100644
--- a/test/Reduce.hs
+++ b/test/Reduce.hs
@@ -1,50 +1,52 @@
-{-|
-Module : Reduce
-Description : Test reduction.
-Copyright : (c) 2019, Yann Herklotz Grave
-License : GPL-3
-Maintainer : yann [at] yannherklotz [dot] com
-Stability : experimental
-Portability : POSIX
-
-Test reduction.
--}
-
{-# LANGUAGE QuasiQuotes #-}
+-- |
+-- Module : Reduce
+-- Description : Test reduction.
+-- Copyright : (c) 2019, Yann Herklotz Grave
+-- License : GPL-3
+-- Maintainer : yann [at] yannherklotz [dot] com
+-- Stability : experimental
+-- Portability : POSIX
+--
+-- Test reduction.
module Reduce
- ( reduceUnitTests
- )
+ ( reduceUnitTests,
+ )
where
-import Data.List ((\\))
-import Test.Tasty
-import Test.Tasty.HUnit
-import Verismith
-import Verismith.Reduce
+import Data.List ((\\))
import Data.Text (Text)
+import Test.Tasty
+import Test.Tasty.HUnit
+import Verismith
+import Verismith.Reduce
-sourceInfo :: Text -> Verilog () -> SourceInfo ()
+sourceInfo :: Text -> Verilog ReduceAnn -> SourceInfo ReduceAnn
sourceInfo = SourceInfo
reduceUnitTests :: TestTree
-reduceUnitTests = testGroup
+reduceUnitTests =
+ testGroup
"Reducer tests"
- [ moduleReducerTest
- , modItemReduceTest
- , halveStatementsTest
- , statementReducerTest
- , activeWireTest
- , cleanTest
- , cleanAllTest
- , removeDeclTest
+ [ moduleReducerTest,
+ modItemReduceTest,
+ halveStatementsTest,
+ statementReducerTest,
+ activeWireTest,
+ cleanTest,
+ cleanAllTest,
+ removeDeclTest
]
removeConstInConcatTest :: TestTree
removeConstInConcatTest = testCase "Remove const in concat" $ do
- GenVerilog (removeDecl srcInfo1) @?= golden1
+ GenVerilog (removeDecl srcInfo1) @?= golden1
where
- srcInfo1 = sourceInfo "top" [verilog|
+ srcInfo1 =
+ sourceInfo
+ "top"
+ [verilog|
module top;
wire a;
reg b;
@@ -57,7 +59,11 @@ module top;
end
endmodule
|]
- golden1 = GenVerilog $ sourceInfo "top" [verilog|
+ golden1 =
+ GenVerilog $
+ sourceInfo
+ "top"
+ [verilog|
module top;
wire a;
reg b;
@@ -73,9 +79,12 @@ endmodule
removeDeclTest :: TestTree
removeDeclTest = testCase "Remove declarations" $ do
- GenVerilog (removeDecl srcInfo1) @?= golden1
- where
- srcInfo1 = sourceInfo "top" [verilog|
+ GenVerilog (removeDecl srcInfo1) @?= golden1
+ where
+ srcInfo1 =
+ sourceInfo
+ "top"
+ [verilog|
module top;
wire a;
wire b;
@@ -103,7 +112,11 @@ module top;
assign b = g;
endmodule
|]
- golden1 = GenVerilog $ sourceInfo "top" [verilog|
+ golden1 =
+ GenVerilog $
+ sourceInfo
+ "top"
+ [verilog|
module top;
wire a;
wire b;
@@ -130,9 +143,12 @@ endmodule
|]
cleanAllTest = testCase "Clean all" $ do
- GenVerilog (cleanSourceInfoAll srcInfo1) @?= golden1
- where
- srcInfo1 = sourceInfo "top" [verilog|
+ GenVerilog (cleanSourceInfoAll srcInfo1) @?= golden1
+ where
+ srcInfo1 =
+ sourceInfo
+ "top"
+ [verilog|
module top;
wire a;
wire b;
@@ -160,7 +176,11 @@ module mod2;
assign b = c + d;
endmodule
|]
- golden1 = GenVerilog $ sourceInfo "top" [verilog|
+ golden1 =
+ GenVerilog $
+ sourceInfo
+ "top"
+ [verilog|
module top;
wire a;
wire b;
@@ -191,10 +211,12 @@ endmodule
cleanTest :: TestTree
cleanTest = testCase "Clean expression" $ do
- clean ["wire1", "wire2"] srcInfo1 @?= golden1
- clean ["wire1", "wire3"] srcInfo2 @?= golden2
- where
- srcInfo1 = GenVerilog . sourceInfo "top" $ [verilog|
+ clean ["wire1", "wire2"] srcInfo1 @?= golden1
+ clean ["wire1", "wire3"] srcInfo2 @?= golden2
+ where
+ srcInfo1 =
+ GenVerilog . sourceInfo "top" $
+ [verilog|
module top;
wire wire1;
wire wire2;
@@ -202,7 +224,9 @@ module top;
assign wire1 = wire2[wire3];
endmodule
|]
- golden1 = GenVerilog . sourceInfo "top" $ [verilog|
+ golden1 =
+ GenVerilog . sourceInfo "top" $
+ [verilog|
module top;
wire wire1;
wire wire2;
@@ -210,7 +234,9 @@ module top;
assign wire1 = wire2[1'b0];
endmodule
|]
- srcInfo2 = GenVerilog . sourceInfo "top" $ [verilog|
+ srcInfo2 =
+ GenVerilog . sourceInfo "top" $
+ [verilog|
module top;
wire wire1;
wire wire2;
@@ -218,7 +244,9 @@ module top;
assign wire1 = wire2[wire3:wire1];
endmodule
|]
- golden2 = GenVerilog . sourceInfo "top" $ [verilog|
+ golden2 =
+ GenVerilog . sourceInfo "top" $
+ [verilog|
module top;
wire wire1;
wire wire2;
@@ -227,15 +255,18 @@ module top;
endmodule
|]
-
activeWireTest :: TestTree
activeWireTest = testCase "Active wires" $ do
- findActiveWires "top" verilog1 \\ ["x", "y", "z", "w"] @?= []
- findActiveWires "top" verilog2 \\ ["x", "y", "z"] @?= []
- findActiveWires "top" verilog3 \\ ["x", "y", "clk", "r1", "r2"] @?= []
- findActiveWires "top" verilog4 \\ ["x", "y", "w", "a", "b"] @?= []
- where
- verilog1 = sourceInfo "top" [verilog|
+ findActiveWires "top" verilog1 \\ ["x", "y", "z", "w"] @?= []
+ findActiveWires "top" verilog2 \\ ["x", "y", "z"] @?= []
+ findActiveWires "top" verilog3 \\ ["x", "y", "clk", "r1", "r2"] @?= []
+ findActiveWires "top" verilog4 \\ ["x", "y", "w", "a", "b"] @?= []
+ findActiveWires "top" verilog5 \\ ["r2", "r1", "x", "y"] @?= []
+ where
+ verilog1 =
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
input x;
output y;
@@ -246,7 +277,10 @@ module top(y, x);
assign y = w + z;
endmodule
|]
- verilog2 = sourceInfo "top" [verilog|
+ verilog2 =
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
input x;
output y;
@@ -255,7 +289,10 @@ module top(y, x);
assign z = 0;
endmodule
|]
- verilog3 = sourceInfo "top" [verilog|
+ verilog3 =
+ sourceInfo
+ "top"
+ [verilog|
module top(clk, y, x);
input clk;
input x;
@@ -276,7 +313,10 @@ module top(clk, y, x);
assign y = {r1, r2, r3};
endmodule
|]
- verilog4 = sourceInfo "top" [verilog|
+ verilog4 =
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
input x;
output y;
@@ -300,12 +340,32 @@ module m2(y, z, x);
output z;
endmodule
|]
+ verilog5 =
+ sourceInfo
+ "top"
+ [verilog|
+module top(y, x);
+ input x;
+ output y;
+ reg r1;
+ reg r2;
+ reg r3;
+ always @* begin
+ for (r1 = 1; r1 < 2; r1 = r1 + 1) begin
+ r2 <= 1'b0;
+ end
+ end
+endmodule
+|]
halveStatementsTest :: TestTree
halveStatementsTest = testCase "Statements" $ do
- GenVerilog <$> halveStatements "top" srcInfo1 @?= golden1
- where
- srcInfo1 = sourceInfo "top" [verilog|
+ GenVerilog <$> halveStatements "top" (tagAlways "top" srcInfo1) @?= golden1
+ where
+ srcInfo1 =
+ sourceInfo
+ "top"
+ [verilog|
module top(clk, y, x);
input clk;
input x;
@@ -327,7 +387,13 @@ module top(clk, y, x);
assign y = {r1, r2, r3};
endmodule
|]
- golden1 = GenVerilog <$> Dual (sourceInfo "top" [verilog|
+ golden1 =
+ GenVerilog
+ <$> Dual
+ ( tagAlways "top" $
+ sourceInfo
+ "top"
+ [verilog|
module top(clk, y, x);
input clk;
input x;
@@ -336,15 +402,22 @@ module top(clk, y, x);
reg r2;
reg r3;
always @(posedge clk) begin
- r1 <= 1'b0;
+ r1 <= r3;
end
always @(posedge clk) begin
- r1 <= 1'b0;
+ r1 <= r2;
+ r2 <= r3;
+ r3 <= r1;
end
- assign y = {r1, 1'b0, 1'b0};
+ assign y = {r1, r2, r3};
endmodule
-|]) (sourceInfo "top" [verilog|
+|]
+ )
+ ( tagAlways "top" $
+ sourceInfo
+ "top"
+ [verilog|
module top(clk, y, x);
input clk;
input x;
@@ -353,23 +426,28 @@ module top(clk, y, x);
reg r2;
reg r3;
always @(posedge clk) begin
- r2 <= 1'b0;
+ r2 <= r1;
r3 <= r2;
end
always @(posedge clk) begin
+ r1 <= r2;
r2 <= r3;
- r3 <= 1'b0;
+ r3 <= r1;
end
- assign y = {1'b0, r2, r3};
+ assign y = {r1, r2, r3};
endmodule
-|])
+|]
+ )
modItemReduceTest :: TestTree
modItemReduceTest = testCase "Module items" $ do
- GenVerilog <$> halveModItems "top" srcInfo1 @?= golden1
- where
- srcInfo1 = sourceInfo "top" [verilog|
+ GenVerilog <$> halveModItems "top" srcInfo1 @?= golden1
+ where
+ srcInfo1 =
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
input x;
output y;
@@ -380,7 +458,12 @@ module top(y, x);
assign y = w;
endmodule
|]
- golden1 = GenVerilog <$> Dual (sourceInfo "top" [verilog|
+ golden1 =
+ GenVerilog
+ <$> Dual
+ ( sourceInfo
+ "top"
+ [verilog|
module top(y, x);
input x;
output y;
@@ -389,7 +472,11 @@ module top(y, x);
assign y = 1'b0;
assign z = x;
endmodule
-|]) (sourceInfo "top" [verilog|
+|]
+ )
+ ( sourceInfo
+ "top"
+ [verilog|
module top(y, x);
input x;
output y;
@@ -398,14 +485,19 @@ module top(y, x);
assign y = w;
assign w = 1'b0;
endmodule
-|])
+|]
+ )
statementReducerTest :: TestTree
statementReducerTest = testCase "Statement reducer" $ do
- GenVerilog <$> halveStatements "top" srcInfo1 @?= fmap GenVerilog golden1
- GenVerilog <$> halveStatements "top" srcInfo2 @?= fmap GenVerilog golden2
- where
- srcInfo1 = sourceInfo "top" [verilog|
+ GenVerilog <$> halveStatements "top" srcInfo1 @?= fmap GenVerilog golden1
+ GenVerilog <$> halveStatements "top" srcInfo2 @?= fmap GenVerilog golden2
+ where
+ srcInfo1 =
+ tagAlways "top" $
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
@@ -425,7 +517,12 @@ module top(y, x);
end
endmodule
|]
- golden1 = Dual (sourceInfo "top" [verilog|
+ golden1 =
+ Dual
+ ( tagAlways "top" $
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
@@ -438,9 +535,16 @@ module top(y, x);
always @(posedge clk) begin
a <= 1;
b <= 2;
+ c <= 3;
+ d <= 4;
end
endmodule
-|]) $ sourceInfo "top" [verilog|
+|]
+ )
+ . tagAlways "top"
+ $ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
@@ -451,12 +555,18 @@ module top(y, x);
end
always @(posedge clk) begin
+ a <= 1;
+ b <= 2;
c <= 3;
d <= 4;
end
endmodule
|]
- srcInfo2 = sourceInfo "top" [verilog|
+ srcInfo2 =
+ tagAlways "top" $
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
@@ -469,7 +579,12 @@ module top(y, x);
end
endmodule
|]
- golden2 = Dual (sourceInfo "top" [verilog|
+ golden2 =
+ Dual
+ ( tagAlways "top" $
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
@@ -477,7 +592,12 @@ module top(y, x);
always @(posedge clk)
y <= 2;
endmodule
-|]) $ sourceInfo "top" [verilog|
+|]
+ )
+ . tagAlways "top"
+ $ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
@@ -489,10 +609,13 @@ endmodule
moduleReducerTest :: TestTree
moduleReducerTest = testCase "Module reducer" $ do
- halveModules srcInfo1 @?= golden1
- halveModules srcInfo2 @?= golden2
- where
- srcInfo1 = sourceInfo "top" [verilog|
+ halveModules srcInfo1 @?= golden1
+ halveModules srcInfo2 @?= golden2
+ where
+ srcInfo1 =
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
@@ -504,13 +627,20 @@ module m(y, x);
input wire [4:0] x;
endmodule
|]
- golden1 = Single $ sourceInfo "top" [verilog|
+ golden1 =
+ Single $
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
endmodule
|]
- srcInfo2 = sourceInfo "top" [verilog|
+ srcInfo2 =
+ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
@@ -528,7 +658,11 @@ module m2(y, x);
input wire [4:0] x;
endmodule
|]
- golden2 = Dual (sourceInfo "top" [verilog|
+ golden2 =
+ Dual
+ ( sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;
@@ -539,7 +673,11 @@ module m(y, x);
output wire [4:0] y;
input wire [4:0] x;
endmodule
-|]) $ sourceInfo "top" [verilog|
+|]
+ )
+ $ sourceInfo
+ "top"
+ [verilog|
module top(y, x);
output wire [4:0] y;
input wire [4:0] x;