aboutsummaryrefslogtreecommitdiffstats
path: root/src/VeriFuzz
diff options
context:
space:
mode:
authorYann Herklotz <ymherklotz@gmail.com>2019-01-10 15:49:13 +0000
committerYann Herklotz <ymherklotz@gmail.com>2019-01-10 15:49:13 +0000
commitdac34f6ff5c46f11fe6c548b92a02ebf4f10d7e9 (patch)
treee51f51b4e82f3c764bcba88725e20e4fb10284da /src/VeriFuzz
parent3f1190cd7fc873449a1fd430386aa4b773d010ac (diff)
downloadverismith-dac34f6ff5c46f11fe6c548b92a02ebf4f10d7e9.tar.gz
verismith-dac34f6ff5c46f11fe6c548b92a02ebf4f10d7e9.zip
Rename files out of the module
Diffstat (limited to 'src/VeriFuzz')
-rw-r--r--src/VeriFuzz/Circuit.hs38
-rw-r--r--src/VeriFuzz/Graph/ASTGen.hs86
-rw-r--r--src/VeriFuzz/Graph/CodeGen.hs60
-rw-r--r--src/VeriFuzz/Graph/Random.hs58
-rw-r--r--src/VeriFuzz/Graph/RandomAlt.hs29
-rw-r--r--src/VeriFuzz/Internal/Gen.hs33
-rw-r--r--src/VeriFuzz/Internal/Shared.hs18
-rw-r--r--src/VeriFuzz/Simulator.hs23
-rw-r--r--src/VeriFuzz/Simulator/General.hs50
-rw-r--r--src/VeriFuzz/Simulator/Icarus.hs66
-rw-r--r--src/VeriFuzz/Simulator/Xst.hs58
-rw-r--r--src/VeriFuzz/Simulator/Yosys.hs94
-rw-r--r--src/VeriFuzz/Verilog.hs28
-rw-r--r--src/VeriFuzz/Verilog/AST.hs461
-rw-r--r--src/VeriFuzz/Verilog/Arbitrary.hs184
-rw-r--r--src/VeriFuzz/Verilog/CodeGen.hs315
-rw-r--r--src/VeriFuzz/Verilog/Helpers.hs75
-rw-r--r--src/VeriFuzz/Verilog/Mutate.hs148
18 files changed, 1824 insertions, 0 deletions
diff --git a/src/VeriFuzz/Circuit.hs b/src/VeriFuzz/Circuit.hs
new file mode 100644
index 0000000..7958f6a
--- /dev/null
+++ b/src/VeriFuzz/Circuit.hs
@@ -0,0 +1,38 @@
+{-|
+Module : VeriFuzz.Circuit
+Description : Definition of the circuit graph.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Definition of the circuit graph.
+-}
+
+module VeriFuzz.Circuit where
+
+import Data.Graph.Inductive (Gr, LNode)
+import System.Random
+import Test.QuickCheck
+
+-- | The types for all the gates.
+data Gate = And
+ | Or
+ | Xor
+ deriving (Show, Eq, Enum, Bounded, Ord)
+
+-- | Newtype for the Circuit which implements a Graph from fgl.
+newtype Circuit = Circuit { getCircuit :: Gr Gate () }
+
+newtype CNode = CNode { getCNode :: LNode Gate }
+
+instance Random Gate where
+ randomR (a, b) g =
+ case randomR (fromEnum a, fromEnum b) g of
+ (x, g') -> (toEnum x, g')
+
+ random = randomR (minBound, maxBound)
+
+instance Arbitrary Gate where
+ arbitrary = elements [And, Or, Xor]
diff --git a/src/VeriFuzz/Graph/ASTGen.hs b/src/VeriFuzz/Graph/ASTGen.hs
new file mode 100644
index 0000000..2b241e1
--- /dev/null
+++ b/src/VeriFuzz/Graph/ASTGen.hs
@@ -0,0 +1,86 @@
+{-|
+Module : VeriFuzz.Graph.ASTGen
+Description : Generates the AST from the graph directly.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Generates the AST from the graph directly.
+-}
+
+module VeriFuzz.Graph.ASTGen where
+
+import Data.Foldable (fold)
+import Data.Graph.Inductive (LNode, Node)
+import qualified Data.Graph.Inductive as G
+import Data.Maybe (catMaybes)
+import qualified Data.Text as T
+import VeriFuzz.Circuit
+import VeriFuzz.Internal.Gen
+import VeriFuzz.Internal.Shared
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.Helpers
+
+-- | Converts a 'CNode' to an 'Identifier'.
+frNode :: Node -> Identifier
+frNode = Identifier . fromNode
+
+-- | Converts a 'Gate' to a 'BinaryOperator', which should be a bijective
+-- mapping.
+fromGate :: Gate -> BinaryOperator
+fromGate And = BinAnd
+fromGate Or = BinOr
+fromGate Xor = BinXor
+
+inputsC :: Circuit -> [Node]
+inputsC c =
+ inputs (getCircuit c)
+
+outputsC :: Circuit -> [Node]
+outputsC c =
+ outputs (getCircuit c)
+
+genPortsAST :: (Circuit -> [Node]) -> Circuit -> [Port]
+genPortsAST f c =
+ port . frNode <$> f c
+ where
+ port = Port Wire 4
+
+-- | Generates the nested expression AST, so that it can then generate the
+-- assignment expressions.
+genAssignExpr :: Gate -> [Node] -> Maybe Expr
+genAssignExpr g [] = Nothing
+genAssignExpr g [n] = Just . Id $ frNode n
+genAssignExpr g (n:ns) = BinOp wire op <$> genAssignExpr g ns
+ where
+ wire = Id $ frNode n
+ op = fromGate g
+
+-- | Generate the continuous assignment AST for a particular node. If it does
+-- not have any nodes that link to it then return 'Nothing', as that means that
+-- the assignment will just be empty.
+genContAssignAST :: Circuit -> LNode Gate -> Maybe ModItem
+genContAssignAST c (n, g) = ModCA . ContAssign name <$> genAssignExpr g nodes
+ where
+ gr = getCircuit c
+ nodes = G.pre gr n
+ name = frNode n
+
+genAssignAST :: Circuit -> [ModItem]
+genAssignAST c = catMaybes $ genContAssignAST c <$> nodes
+ where
+ gr = getCircuit c
+ nodes = G.labNodes gr
+
+genModuleDeclAST :: Circuit -> ModDecl
+genModuleDeclAST c = ModDecl id output ports items
+ where
+ id = Identifier "gen_module"
+ ports = genPortsAST inputsC c
+ output = [Port Wire 90 "y"]
+ items = genAssignAST c ++ [ModCA . ContAssign "y" . fold $ portToExpr <$> ports]
+
+generateAST :: Circuit -> VerilogSrc
+generateAST c = VerilogSrc [Description $ genModuleDeclAST c]
diff --git a/src/VeriFuzz/Graph/CodeGen.hs b/src/VeriFuzz/Graph/CodeGen.hs
new file mode 100644
index 0000000..0d23044
--- /dev/null
+++ b/src/VeriFuzz/Graph/CodeGen.hs
@@ -0,0 +1,60 @@
+{-|
+Module : VeriFuzz.Graph.Random
+Description : Code generation directly from DAG.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Define the code generation directly from the random DAG.
+-}
+
+module VeriFuzz.Graph.CodeGen
+ ( generate
+ ) where
+
+import Data.Foldable (fold)
+import Data.Graph.Inductive (Graph, LNode, Node, indeg, labNodes,
+ nodes, outdeg, pre)
+import Data.Maybe (fromMaybe)
+import Data.Text (Text)
+import qualified Data.Text as T
+import VeriFuzz.Circuit
+import VeriFuzz.Internal.Gen
+import VeriFuzz.Internal.Shared
+
+toOperator :: Gate -> Text
+toOperator And = " & "
+toOperator Or = " | "
+toOperator Xor = " ^ "
+
+statList :: Gate -> [Node] -> Maybe Text
+statList g n = toStr <$> safe tail n
+ where
+ toStr = fold . fmap ((<> toOperator g) . fromNode)
+
+lastEl :: [Node] -> Maybe Text
+lastEl n = fromNode <$> safe head n
+
+toStmnt :: (Graph gr) => gr Gate e -> LNode Gate -> Text
+toStmnt graph (n, g) =
+ fromMaybe T.empty $ Just " assign " <> Just (fromNode n)
+ <> Just " = " <> statList g nodeL <> lastEl nodeL <> Just ";\n"
+ where
+ nodeL = pre graph n
+
+generate :: (Graph gr) => gr Gate e -> Text
+generate graph =
+ "module generated_module(\n"
+ <> fold (imap " input wire " ",\n" inp)
+ <> T.intercalate ",\n" (imap " output wire " "" out)
+ <> ");\n"
+ <> fold (toStmnt graph <$> labNodes graph)
+ <> "endmodule\n\nmodule main;\n initial\n begin\n "
+ <> "$display(\"Hello, world\");\n $finish;\n "
+ <> "end\nendmodule"
+ where
+ inp = inputs graph
+ out = outputs graph
+ imap b e = fmap ((\s -> b <> s <> e) . fromNode)
diff --git a/src/VeriFuzz/Graph/Random.hs b/src/VeriFuzz/Graph/Random.hs
new file mode 100644
index 0000000..0514f6d
--- /dev/null
+++ b/src/VeriFuzz/Graph/Random.hs
@@ -0,0 +1,58 @@
+{-|
+Module : VeriFuzz.Graph.Random
+Description : Random generation for DAG
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Define the random generation for the directed acyclic graph.
+-}
+
+module VeriFuzz.Graph.Random where
+
+import Data.Graph.Inductive (Context, Graph, LEdge)
+import qualified Data.Graph.Inductive as G
+import Data.Graph.Inductive.PatriciaTree (Gr)
+import Data.List (nub)
+import Test.QuickCheck (Arbitrary, Gen)
+import qualified Test.QuickCheck as QC
+
+dupFolder :: (Eq a, Eq b) => Context a b -> [Context a b] -> [Context a b]
+dupFolder cont ns =
+ unique cont : ns
+ where
+ unique (a, b, c, d) = (nub a, b, c, nub d)
+
+-- | Remove duplicates.
+rDups :: (Eq a, Eq b) => Gr a b -> Gr a b
+rDups g = G.buildGr $ G.ufold dupFolder [] g
+
+-- | Gen instance to create an arbitrary edge, where the edges are limited by
+-- `n` that is passed to it.
+arbitraryEdge :: (Arbitrary e) => Int -> Gen (LEdge e)
+arbitraryEdge n = do
+ x <- with $ \a -> a < n && a > 0 && a /= n-1
+ y <- with $ \a -> x < a && a < n && a > 0
+ z <- QC.arbitrary
+ return (x, y, z)
+ where
+ with = QC.suchThat $ QC.resize n QC.arbitrary
+
+-- | Gen instance for a random acyclic DAG.
+randomDAG :: (Arbitrary l, Arbitrary e, Eq l, Eq e)
+ => Gen (Gr l e) -- ^ The generated graph. It uses Arbitrary to
+ -- generate random instances of each node
+randomDAG = do
+ list <- QC.infiniteListOf QC.arbitrary
+ l <- QC.infiniteListOf aE
+ QC.sized (\n -> return . G.mkGraph (nodes list n) $ take (10*n) l)
+ where
+ nodes l n = zip [0..n] $ take n l
+ aE = QC.sized arbitraryEdge
+
+-- | Generate a random acyclic DAG with an IO instance.
+genRandomDAG :: (Arbitrary l, Arbitrary e, Eq l, Eq e)
+ => IO (Gr l e)
+genRandomDAG = QC.generate randomDAG
diff --git a/src/VeriFuzz/Graph/RandomAlt.hs b/src/VeriFuzz/Graph/RandomAlt.hs
new file mode 100644
index 0000000..d9ee138
--- /dev/null
+++ b/src/VeriFuzz/Graph/RandomAlt.hs
@@ -0,0 +1,29 @@
+{-|p
+Module : VeriFuzz.Graph.RandomAlt
+Description : RandomAlt generation for DAG
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Define the random generation for the directed acyclic graph.
+-}
+
+module VeriFuzz.Graph.RandomAlt where
+
+import Data.Graph.Inductive (Graph, LEdge, mkGraph)
+import qualified Data.Graph.Inductive.Arbitrary as G
+import Data.Graph.Inductive.PatriciaTree (Gr)
+import Test.QuickCheck (Arbitrary, Gen)
+import qualified Test.QuickCheck as QC
+
+randomDAG :: (Arbitrary l, Arbitrary e)
+ => Gen (Gr l e)
+randomDAG =
+ G.looplessGraph <$> QC.arbitrary
+
+-- | Generate a random acyclic DAG with an IO instance.
+genRandomDAG :: (Arbitrary l, Arbitrary e)
+ => IO (Gr l e)
+genRandomDAG = QC.generate randomDAG
diff --git a/src/VeriFuzz/Internal/Gen.hs b/src/VeriFuzz/Internal/Gen.hs
new file mode 100644
index 0000000..be275dd
--- /dev/null
+++ b/src/VeriFuzz/Internal/Gen.hs
@@ -0,0 +1,33 @@
+{-|
+Module : VeriFuzz.Internal.Gen
+Description : Internal helpers for generation.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Internal helpers for generation.
+-}
+
+module VeriFuzz.Internal.Gen where
+
+import Data.Graph.Inductive (Graph, Node)
+import qualified Data.Graph.Inductive as G
+import qualified Data.Text as T
+
+fromNode :: Int -> T.Text
+fromNode node = T.pack $ "w" <> show node
+
+filterGr :: (Graph gr) => gr n e -> (Node -> Bool) -> [Node]
+filterGr graph f =
+ filter f $ G.nodes graph
+
+only :: (Graph gr) => gr n e -> (gr n e -> Node -> Int) -> (gr n e -> Node -> Int) -> Node -> Bool
+only graph fun1 fun2 n = fun1 graph n == 0 && fun2 graph n /= 0
+
+inputs :: (Graph gr) => gr n e -> [Node]
+inputs graph = filterGr graph $ only graph G.indeg G.outdeg
+
+outputs :: (Graph gr) => gr n e -> [Node]
+outputs graph = filterGr graph $ only graph G.outdeg G.indeg
diff --git a/src/VeriFuzz/Internal/Shared.hs b/src/VeriFuzz/Internal/Shared.hs
new file mode 100644
index 0000000..c7d2760
--- /dev/null
+++ b/src/VeriFuzz/Internal/Shared.hs
@@ -0,0 +1,18 @@
+{-|
+Module : VeriFuzz.Internal.Shared
+Description : Shared high level code used in the other modules internally.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Shared high level code used in the other modules internally.
+-}
+
+module VeriFuzz.Internal.Shared where
+
+-- | Converts unsafe list functions in the Prelude to a safe version.
+safe :: ([a] -> b) -> [a] -> Maybe b
+safe _ [] = Nothing
+safe f l = Just $ f l
diff --git a/src/VeriFuzz/Simulator.hs b/src/VeriFuzz/Simulator.hs
new file mode 100644
index 0000000..cadaffd
--- /dev/null
+++ b/src/VeriFuzz/Simulator.hs
@@ -0,0 +1,23 @@
+{-|
+Module : Test.VeriFuzz.Simulator
+Description : Simulator module.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Simulator module.
+-}
+
+module Test.VeriFuzz.Simulator
+ ( module Test.VeriFuzz.Simulator.General
+ , module Test.VeriFuzz.Simulator.Yosys
+ , module Test.VeriFuzz.Simulator.Xst
+ , module Test.VeriFuzz.Simulator.Icarus
+ ) where
+
+import Test.VeriFuzz.Simulator.General
+import Test.VeriFuzz.Simulator.Icarus
+import Test.VeriFuzz.Simulator.Xst
+import Test.VeriFuzz.Simulator.Yosys
diff --git a/src/VeriFuzz/Simulator/General.hs b/src/VeriFuzz/Simulator/General.hs
new file mode 100644
index 0000000..a024029
--- /dev/null
+++ b/src/VeriFuzz/Simulator/General.hs
@@ -0,0 +1,50 @@
+{-|
+Module : VeriFuzz.Simulator.General
+Description : Class of the simulator.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Class of the simulator and the synthesize tool.
+-}
+
+module VeriFuzz.Simulator.General where
+
+import Data.Bits (shiftL)
+import Data.ByteString (ByteString)
+import qualified Data.ByteString as B
+import Data.Text (Text)
+import Prelude hiding (FilePath)
+import Shelly
+import VeriFuzz.Verilog.AST
+
+-- | Simulator class.
+class Simulator a where
+ toText :: a -> Text
+
+-- | Simulation type class.
+class (Simulator a) => Simulate a where
+ runSim :: a -- ^ Simulator instance
+ -> ModDecl -- ^ Module to simulate
+ -> [ByteString] -- ^ Inputs to simulate
+ -> Sh Int -- ^ Returns the value of the hash at the output of the testbench.
+
+-- | Synthesize type class.
+class (Simulator a) => Synthesize a where
+ runSynth :: a -- ^ Synthesize tool instance
+ -> ModDecl -- ^ Module to synthesize
+ -> FilePath -- ^ Output verilog file for the module
+ -> Sh () -- ^ does not return any values
+
+timeout :: FilePath -> [Text] -> Sh Text
+timeout = command1 "timeout" ["180"] . toTextIgnore
+
+timeout_ :: FilePath -> [Text] -> Sh ()
+timeout_ = command1_ "timeout" ["180"] . toTextIgnore
+
+-- | Helper function to convert bytestrings to integers
+bsToI :: ByteString -> Integer
+bsToI = B.foldl' (\i b -> (i `shiftL` 8) + fromIntegral b) 0
+{-# INLINE bsToI #-}
diff --git a/src/VeriFuzz/Simulator/Icarus.hs b/src/VeriFuzz/Simulator/Icarus.hs
new file mode 100644
index 0000000..744deb8
--- /dev/null
+++ b/src/VeriFuzz/Simulator/Icarus.hs
@@ -0,0 +1,66 @@
+{-|
+Module : VeriFuzz.Simulator.Icarus
+Description : Icarus verilog module.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Icarus verilog module.
+-}
+
+module VeriFuzz.Simulator.Icarus where
+
+import Control.Lens
+import Data.ByteString (ByteString)
+import qualified Data.ByteString as B
+import Data.Foldable (fold)
+import Data.Hashable
+import Data.List (transpose)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Prelude hiding (FilePath)
+import Shelly
+import Text.Shakespeare.Text (st)
+import VeriFuzz.Simulator.General
+import VeriFuzz.Verilog
+
+data Icarus = Icarus { icarusPath :: FilePath
+ , vvpPath :: FilePath
+ }
+
+instance Simulator Icarus where
+ toText _ = "iverilog"
+
+instance Simulate Icarus where
+ runSim = runSimIcarus
+
+defaultIcarus :: Icarus
+defaultIcarus = Icarus "iverilog" "vvp"
+
+addDisplay :: [Stmnt] -> [Stmnt]
+addDisplay s =
+ concat $ transpose [s, replicate l $ TimeCtrl 1 Nothing
+ , replicate l . SysTaskEnable $ Task "display" ["%h", Id "y"]]
+ where
+ l = length s
+
+assignFunc :: [Port] -> ByteString -> Stmnt
+assignFunc inp bs =
+ NonBlockAssign . Assign conc Nothing . Number (B.length bs * 4) $ bsToI bs
+ where
+ conc = RegConcat (portToExpr <$> inp)
+
+runSimIcarus :: Icarus -> ModDecl -> [ByteString] -> Sh Int
+runSimIcarus sim m bss = do
+ let tb = ModDecl "main" [] []
+ [ Initial $
+ fold (addDisplay $ assignFunc (m ^. modInPorts) <$> bss)
+ <> (SysTaskEnable $ Task "finish" [])
+ ]
+ let newtb = instantiateMod m tb
+ let modWithTb = VerilogSrc $ Description <$> [newtb, m]
+ writefile "main.v" $ genSource modWithTb
+ run_ (icarusPath sim) ["-o", "main", "main.v"]
+ hash <$> run (vvpPath sim) ["main"]
diff --git a/src/VeriFuzz/Simulator/Xst.hs b/src/VeriFuzz/Simulator/Xst.hs
new file mode 100644
index 0000000..902b244
--- /dev/null
+++ b/src/VeriFuzz/Simulator/Xst.hs
@@ -0,0 +1,58 @@
+{-|
+Module : VeriFuzz.Simulator.Xst
+Description : Xst (ise) simulator implementation.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Xst (ise) simulator implementation.
+-}
+
+{-# LANGUAGE QuasiQuotes #-}
+
+module VeriFuzz.Simulator.Xst where
+
+import Control.Lens hiding ((<.>))
+import Data.Text (Text)
+import qualified Data.Text as T
+import Prelude hiding (FilePath)
+import Shelly
+import Text.Shakespeare.Text (st)
+import VeriFuzz.Simulator.General
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.CodeGen
+
+data Xst = Xst { xstPath :: FilePath
+ , netgenPath :: FilePath
+ }
+
+instance Simulator Xst where
+ toText _ = "xst"
+
+instance Synthesize Xst where
+ runSynth = runSynthXst
+
+defaultXst :: Xst
+defaultXst = Xst "/opt/Xilinx/14.7/ISE_DS/ISE/bin/lin64/xst" "/opt/Xilinx/14.7/ISE_DS/ISE/bin/lin64/netgen"
+
+runSynthXst :: Xst -> ModDecl -> FilePath -> Sh ()
+runSynthXst sim mod outf = do
+ writefile xstFile [st|run
+-ifn #{modName}.prj -ofn #{modName} -p artix7 -top #{modName}
+-iobuf NO -ram_extract NO -rom_extract NO -use_dsp48 NO
+-fsm_extract YES -fsm_encoding Auto
+-change_error_to_warning "HDLCompiler:226 HDLCompiler:1832"
+|]
+ writefile prjFile [st|verilog work "rtl.v"|]
+ writefile "rtl.v" $ genSource mod
+ timeout_ (xstPath sim) ["-ifn", toTextIgnore xstFile]
+ run_ (netgenPath sim) ["-w", "-ofmt", "verilog", toTextIgnore $ modFile <.> "ngc", toTextIgnore outf]
+ run_ "sed" ["-i", "/^`ifndef/,/^`endif/ d; s/ *Timestamp: .*//;", toTextIgnore outf]
+ where
+ modName = mod ^. moduleId . getIdentifier
+ modFile = fromText modName
+ xstFile = modFile <.> "xst"
+ prjFile = modFile <.> "prj"
+ vFile = modFile <.> "v"
diff --git a/src/VeriFuzz/Simulator/Yosys.hs b/src/VeriFuzz/Simulator/Yosys.hs
new file mode 100644
index 0000000..3ac732d
--- /dev/null
+++ b/src/VeriFuzz/Simulator/Yosys.hs
@@ -0,0 +1,94 @@
+{-|
+Module : VeriFuzz.Simulator.Yosys
+Description : Yosys simulator implementation.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Yosys simulator implementation.
+-}
+
+{-# LANGUAGE QuasiQuotes #-}
+
+module VeriFuzz.Simulator.Yosys where
+
+import Control.Lens
+import Data.ByteString (ByteString)
+import qualified Data.ByteString as B
+import Data.Maybe (fromMaybe)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Prelude hiding (FilePath)
+import Shelly
+import Text.Shakespeare.Text (st)
+import VeriFuzz.Simulator.General
+import VeriFuzz.Verilog
+
+newtype Yosys = Yosys { yosysPath :: FilePath }
+
+instance Simulator Yosys where
+ toText _ = "yosys"
+
+instance Simulate Yosys where
+ runSim = runSimYosys
+
+instance Synthesize Yosys where
+ runSynth = runSynthYosys
+
+defaultYosys :: Yosys
+defaultYosys = Yosys "/usr/bin/yosys"
+
+writeSimFile :: Yosys -- ^ Simulator instance
+ -> ModDecl -- ^ Current module
+ -> FilePath -- ^ Output sim file
+ -> Sh ()
+writeSimFile sim m file = do
+ writefile "rtl.v" $ genSource m
+ writefile file [st|read_verilog rtl.v; proc;;
+rename mod mod_rtl
+|]
+
+runSimYosys :: Yosys -> ModDecl -> [ByteString] -> Sh Int
+runSimYosys sim ver tb = return 0
+
+runSynthYosys :: Yosys -> ModDecl -> FilePath -> Sh ()
+runSynthYosys sim m outf = do
+ writefile inpf $ genSource m
+ run_ (yosysPath sim) ["-q", "-b", "verilog -noattr", "-o", out, "-S", inp]
+ where
+ inpf = "rtl.v"
+ inp = toTextIgnore inpf
+ out = toTextIgnore outf
+
+writeSatFile :: (Synthesize a, Synthesize b) => Text -> a -> Maybe b -> ModDecl -> Sh ()
+writeSatFile checkFile sim1 sim2 m =
+ writefile (fromText checkFile) [st|read_verilog syn_#{toText sim1}.v
+rename #{modName} #{modName}_1
+read_verilog syn_#{idSim2}.v
+rename #{modName} #{modName}_2
+read_verilog top.v
+proc; opt_clean
+flatten #{modName}
+! touch test.#{toText sim1}.#{idSim2}.input_ok
+sat -timeout 20 -verify-no-timeout -ignore_div_by_zero -prove y_1 y_2 #{modName}
+|]
+ where
+ idSim2 = maybe "rtl" toText sim2
+ modName = m ^. moduleId . getIdentifier
+ ids = T.intercalate "," $ allVars m ^.. traverse . getIdentifier
+
+runOtherSynth :: (Synthesize a) => Maybe a -> ModDecl -> Sh ()
+runOtherSynth (Just sim) m = runSynth sim m $ fromText [st|syn_#{toText sim}.v|]
+runOtherSynth Nothing m = writefile "syn_rtl.v" $ genSource m
+
+runEquiv :: (Synthesize a, Synthesize b) => Yosys -> a -> Maybe b -> ModDecl -> Sh ()
+runEquiv yosys sim1 sim2 m = do
+ writefile "top.v" . genSource . initMod $ makeTop 2 m
+ writeSatFile checkFile sim1 sim2 m
+ runSynth sim1 m $ fromText [st|syn_#{toText sim1}.v|]
+ runOtherSynth sim2 m
+ run_ (yosysPath yosys) [checkFile]
+ where
+ checkFile = [st|test.#{toText sim1}.#{maybe "rtl" toText sim2}.ys|]
diff --git a/src/VeriFuzz/Verilog.hs b/src/VeriFuzz/Verilog.hs
new file mode 100644
index 0000000..d88f885
--- /dev/null
+++ b/src/VeriFuzz/Verilog.hs
@@ -0,0 +1,28 @@
+{-|
+Module : Test.VeriFuzz.Verilog
+Description : The main verilog module with the syntax and code generation.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+The main verilog module with the syntax and code generation.
+-}
+
+module Test.VeriFuzz.Verilog
+ ( -- * AST
+ module Test.VeriFuzz.Verilog.AST
+ -- * Code Generation
+ , module Test.VeriFuzz.Verilog.CodeGen
+ -- * Verilog mutations
+ , module Test.VeriFuzz.Verilog.Mutate
+ , module Test.VeriFuzz.Verilog.Helpers
+ , module Test.VeriFuzz.Verilog.Arbitrary
+ ) where
+
+import Test.VeriFuzz.Verilog.Arbitrary
+import Test.VeriFuzz.Verilog.AST
+import Test.VeriFuzz.Verilog.CodeGen
+import Test.VeriFuzz.Verilog.Helpers
+import Test.VeriFuzz.Verilog.Mutate
diff --git a/src/VeriFuzz/Verilog/AST.hs b/src/VeriFuzz/Verilog/AST.hs
new file mode 100644
index 0000000..63b1923
--- /dev/null
+++ b/src/VeriFuzz/Verilog/AST.hs
@@ -0,0 +1,461 @@
+{-|
+Module : VeriFuzz.Verilog.AST
+Description : Definition of the Verilog AST types.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Poratbility : POSIX
+
+Defines the types to build a Verilog AST.
+-}
+
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE TemplateHaskell #-}
+
+module VeriFuzz.Verilog.AST where
+
+import Control.Lens (makeLenses, (^.))
+import Data.String (IsString, fromString)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Traversable (sequenceA)
+import qualified QuickCheck as QC
+
+-- | 'Source' class which determines that source code is able to be generated
+-- from the data structure using 'genSource'. This will be stored in 'Text' and
+-- can then be processed further.
+class Source a where
+ genSource :: a -> Text
+
+positiveArb :: (QC.Arbitrary a, Ord a, Num a) => QC.Gen a
+positiveArb = QC.suchThat QC.arbitrary (>0)
+
+instance QC.Arbitrary Text where
+ arbitrary = T.pack <$> QC.arbitrary
+
+-- | Identifier in Verilog. This is just a string of characters that can either
+-- be lowercase and uppercase for now. This might change in the future though,
+-- as Verilog supports many more characters in Identifiers.
+newtype Identifier = Identifier { _getIdentifier :: Text }
+ deriving (Eq, IsString, Semigroup, Monoid)
+
+makeLenses ''Identifier
+
+instance Show Identifier where
+ show i = T.unpack $ i ^. getIdentifier
+
+instance QC.Arbitrary Identifier where
+ arbitrary = do
+ l <- QC.choose (2, 10)
+ Identifier . T.pack <$> replicateM l (QC.elements ['a'..'z'])
+
+-- | Verilog syntax for adding a delay, which is represented as @#num@.
+newtype Delay = Delay { _delay :: Int }
+ deriving (Eq)
+
+instance Num Delay where
+ Delay a + Delay b = Delay $ a + b
+ Delay a - Delay b = Delay $ a - b
+ Delay a * Delay b = Delay $ a * b
+ negate (Delay a) = Delay $ negate a
+ abs (Delay a) = Delay $ abs a
+ signum (Delay a) = Delay $ signum a
+ fromInteger = Delay . fromInteger
+
+instance QC.Arbitrary Delay where
+ arbitrary = Delay <$> positiveArb
+
+-- | Verilog syntax for an event, such as @\@x@, which is used for always blocks
+data Event = EId Identifier
+ | EExpr Expr
+ | EAll
+ deriving (Eq)
+
+instance QC.Arbitrary Event where
+ arbitrary = EId <$> QC.arbitrary
+
+-- | Binary operators that are currently supported in the verilog generation.
+data BinaryOperator = BinPlus -- ^ @+@
+ | BinMinus -- ^ @-@
+ | BinTimes -- ^ @*@
+ | BinDiv -- ^ @/@
+ | BinMod -- ^ @%@
+ | BinEq -- ^ @==@
+ | BinNEq -- ^ @!=@
+ | BinCEq -- ^ @===@
+ | BinCNEq -- ^ @!==@
+ | BinLAnd -- ^ @&&@
+ | BinLOr -- ^ @||@
+ | BinLT -- ^ @<@
+ | BinLEq -- ^ @<=@
+ | BinGT -- ^ @>@
+ | BinGEq -- ^ @>=@
+ | BinAnd -- ^ @&@
+ | BinOr -- ^ @|@
+ | BinXor -- ^ @^@
+ | BinXNor -- ^ @^~@
+ | BinXNorInv -- ^ @~^@
+ | BinPower -- ^ @**@
+ | BinLSL -- ^ @<<@
+ | BinLSR -- ^ @>>@
+ | BinASL -- ^ @<<<@
+ | BinASR -- ^ @>>>@
+ deriving (Eq)
+
+instance QC.Arbitrary BinaryOperator where
+ arbitrary = QC.elements
+ [ BinPlus
+ , BinMinus
+ , BinTimes
+ , BinDiv
+ , BinMod
+ , BinEq
+ , BinNEq
+ , BinCEq
+ , BinCNEq
+ , BinLAnd
+ , BinLOr
+ , BinLT
+ , BinLEq
+ , BinGT
+ , BinGEq
+ , BinAnd
+ , BinOr
+ , BinXor
+ , BinXNor
+ , BinXNorInv
+ , BinPower
+ , BinLSL
+ , BinLSR
+ , BinASL
+ , BinASR
+ ]
+
+-- | Unary operators that are currently supported by the generator.
+data UnaryOperator = UnPlus -- ^ @+@
+ | UnMinus -- ^ @-@
+ | UnNot -- ^ @!@
+ | UnAnd -- ^ @&@
+ | UnNand -- ^ @~&@
+ | UnOr -- ^ @|@
+ | UnNor -- ^ @~|@
+ | UnXor -- ^ @^@
+ | UnNxor -- ^ @~^@
+ | UnNxorInv -- ^ @^~@
+ deriving (Eq)
+
+instance QC.Arbitrary UnaryOperator where
+ arbitrary = QC.elements
+ [ UnPlus
+ , UnMinus
+ , UnNot
+ , UnAnd
+ , UnNand
+ , UnOr
+ , UnNor
+ , UnXor
+ , UnNxor
+ , UnNxorInv
+ ]
+
+-- | Verilog expression, which can either be a primary expression, unary
+-- expression, binary operator expression or a conditional expression.
+data Expr = Number { _numSize :: Int
+ , _numVal :: Integer
+ }
+ | Id { _exprId :: Identifier }
+ | Concat { _concatExpr :: [Expr] }
+ | UnOp { _exprUnOp :: UnaryOperator
+ , _exprPrim :: Expr
+ }
+ | BinOp { _exprLhs :: Expr
+ , _exprBinOp :: BinaryOperator
+ , _exprRhs :: Expr
+ }
+ | Cond { _exprCond :: Expr
+ , _exprTrue :: Expr
+ , _exprFalse :: Expr
+ }
+ | Str { _exprStr :: Text }
+ deriving (Eq)
+
+instance Num Expr where
+ a + b = BinOp a BinPlus b
+ a - b = BinOp a BinMinus b
+ a * b = BinOp a BinTimes b
+ negate = UnOp UnMinus
+ abs = undefined
+ signum = undefined
+ fromInteger = Number 32 . fromInteger
+
+instance Semigroup Expr where
+ (Concat a) <> (Concat b) = Concat $ a <> b
+ (Concat a) <> b = Concat $ a <> [b]
+ a <> (Concat b) = Concat $ a : b
+ a <> b = Concat [a, b]
+
+instance Monoid Expr where
+ mempty = Concat []
+
+instance IsString Expr where
+ fromString = Str . fromString
+
+expr :: Int -> QC.Gen Expr
+expr 0 = QC.oneof
+ [ Id <$> QC.arbitrary
+ , Number <$> positiveArb <*> QC.arbitrary
+ , UnOp <$> QC.arbitrary <*> QC.arbitrary
+ -- , Str <$> QC.arbitrary
+ ]
+expr n
+ | n > 0 = QC.oneof
+ [ Id <$> QC.arbitrary
+ , Number <$> positiveArb <*> QC.arbitrary
+ , Concat <$> QC.listOf1 (subexpr 4)
+ , UnOp <$> QC.arbitrary <*> QC.arbitrary
+ -- , Str <$> QC.arbitrary
+ , BinOp <$> subexpr 2 <*> QC.arbitrary <*> subexpr 2
+ , Cond <$> subexpr 3 <*> subexpr 3 <*> subexpr 3
+ ]
+ | otherwise = expr 0
+ where
+ subexpr y = expr (n `div` y)
+
+instance QC.Arbitrary Expr where
+ arbitrary = QC.sized expr
+
+traverseExpr :: (Applicative f) => (Expr -> f Expr) -> Expr -> f Expr
+traverseExpr f (Concat e) = Concat <$> sequenceA (f <$> e)
+traverseExpr f (UnOp un e) = UnOp un <$> f e
+traverseExpr f (BinOp l op r) = BinOp <$> f l <*> pure op <*> f r
+traverseExpr f (Cond c l r) = Cond <$> f c <*> f l <*> f r
+traverseExpr _ e = pure e
+
+makeLenses ''Expr
+
+-- | Constant expression, which are known before simulation at compilation time.
+newtype ConstExpr = ConstExpr { _constNum :: Int }
+ deriving (Eq, Num)
+
+instance QC.Arbitrary ConstExpr where
+ arbitrary = ConstExpr <$> positiveArb
+
+-- | Type that represents the left hand side of an assignment, which can be a
+-- concatenation such as in:
+--
+-- @
+-- {a, b, c} = 32'h94238;
+-- @
+data LVal = RegId Identifier
+ | RegExpr { _regExprId :: Identifier
+ , _regExpr :: Expr
+ }
+ | RegSize { _regSizeId :: Identifier
+ , _regSizeMSB :: ConstExpr
+ , _regSizeLSB :: ConstExpr
+ }
+ | RegConcat { _regConc :: [Expr] }
+ deriving (Eq)
+
+makeLenses ''LVal
+
+instance QC.Arbitrary LVal where
+ arbitrary = QC.oneof [ RegId <$> QC.arbitrary
+ , RegExpr <$> QC.arbitrary <*> QC.arbitrary
+ , RegSize <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
+ ]
+
+-- | Different port direction that are supported in Verilog.
+data PortDir = PortIn -- ^ Input direction for port (@input@).
+ | PortOut -- ^ Output direction for port (@output@).
+ | PortInOut -- ^ Inout direction for port (@inout@).
+ deriving (Eq)
+
+instance QC.Arbitrary PortDir where
+ arbitrary = QC.elements [PortIn, PortOut, PortInOut]
+
+-- | Currently, only @wire@ and @reg@ are supported, as the other net types are
+-- not that common and not a priority.
+data PortType = Wire
+ | Reg { _regSigned :: Bool }
+ deriving (Eq)
+
+instance QC.Arbitrary PortType where
+ arbitrary = QC.oneof [pure Wire, Reg <$> QC.arbitrary]
+
+makeLenses ''PortType
+
+-- | Port declaration. It contains information about the type of the port, the
+-- size, and the port name. It used to also contain information about if it was
+-- an input or output port. However, this is not always necessary and was more
+-- cumbersome than useful, as a lot of ports can be declared without input and
+-- output port.
+--
+-- This is now implemented inside 'ModDecl' itself, which uses a list of output
+-- and input ports.
+data Port = Port { _portType :: PortType
+ , _portSize :: Int
+ , _portName :: Identifier
+ } deriving (Eq)
+
+makeLenses ''Port
+
+instance QC.Arbitrary Port where
+ arbitrary = Port <$> QC.arbitrary <*> positiveArb <*> QC.arbitrary
+
+-- | This is currently a type because direct module declaration should also be
+-- added:
+--
+-- @
+-- mod a(.y(y1), .x1(x11), .x2(x22));
+-- @
+newtype ModConn = ModConn { _modConn :: Expr }
+ deriving (Eq)
+
+makeLenses ''ModConn
+
+instance QC.Arbitrary ModConn where
+ arbitrary = ModConn <$> QC.arbitrary
+
+data Assign = Assign { _assignReg :: LVal
+ , _assignDelay :: Maybe Delay
+ , _assignExpr :: Expr
+ } deriving (Eq)
+
+instance QC.Arbitrary Assign where
+ arbitrary = Assign <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
+
+data ContAssign = ContAssign { _contAssignNetLVal :: Identifier
+ , _contAssignExpr :: Expr
+ } deriving (Eq)
+
+makeLenses ''ContAssign
+
+instance QC.Arbitrary ContAssign where
+ arbitrary = ContAssign <$> QC.arbitrary <*> QC.arbitrary
+
+-- | Stmnts in Verilog.
+data Stmnt = TimeCtrl { _statDelay :: Delay
+ , _statDStat :: Maybe Stmnt
+ } -- ^ Time control (@#NUM@)
+ | EventCtrl { _statEvent :: Event
+ , _statEStat :: Maybe Stmnt
+ }
+ | SeqBlock { _statements :: [Stmnt] } -- ^ Sequential block (@begin ... end@)
+ | BlockAssign Assign -- ^ blocking assignment (@=@)
+ | NonBlockAssign Assign -- ^ Non blocking assignment (@<=@)
+ | StatCA ContAssign -- ^ Stmnt continuous assignment. May not be correct.
+ | TaskEnable Task
+ | SysTaskEnable Task
+ deriving (Eq)
+
+instance Semigroup Stmnt where
+ (SeqBlock a) <> (SeqBlock b) = SeqBlock $ a <> b
+ (SeqBlock a) <> b = SeqBlock $ a <> [b]
+ a <> (SeqBlock b) = SeqBlock $ a : b
+ a <> b = SeqBlock [a, b]
+
+instance Monoid Stmnt where
+ mempty = SeqBlock []
+
+statement :: Int -> QC.Gen Stmnt
+statement 0 = QC.oneof
+ [ BlockAssign <$> QC.arbitrary
+ , NonBlockAssign <$> QC.arbitrary
+ -- , StatCA <$> QC.arbitrary
+ , TaskEnable <$> QC.arbitrary
+ , SysTaskEnable <$> QC.arbitrary
+ ]
+statement n
+ | n > 0 = QC.oneof
+ [ TimeCtrl <$> QC.arbitrary <*> (Just <$> substat 2)
+ , SeqBlock <$> QC.listOf1 (substat 4)
+ , BlockAssign <$> QC.arbitrary
+ , NonBlockAssign <$> QC.arbitrary
+ -- , StatCA <$> QC.arbitrary
+ , TaskEnable <$> QC.arbitrary
+ , SysTaskEnable <$> QC.arbitrary
+ ]
+ | otherwise = statement 0
+ where
+ substat y = statement (n `div` y)
+
+instance QC.Arbitrary Stmnt where
+ arbitrary = QC.sized statement
+
+data Task = Task { _taskName :: Identifier
+ , _taskExpr :: [Expr]
+ } deriving (Eq)
+
+makeLenses ''Task
+
+instance QC.Arbitrary Task where
+ arbitrary = Task <$> QC.arbitrary <*> QC.arbitrary
+
+-- | Module item which is the body of the module expression.
+data ModItem = ModCA ContAssign
+ | ModInst { _modInstId :: Identifier
+ , _modInstName :: Identifier
+ , _modInstConns :: [ModConn]
+ }
+ | Initial Stmnt
+ | Always Stmnt
+ | Decl { declDir :: Maybe PortDir
+ , declPort :: Port
+ }
+ deriving (Eq)
+
+makeLenses ''ModItem
+
+instance QC.Arbitrary ModItem where
+ arbitrary = QC.oneof [ ModCA <$> QC.arbitrary
+ , ModInst <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
+ , Initial <$> QC.arbitrary
+ , Always <$> (EventCtrl <$> QC.arbitrary <*> QC.arbitrary)
+ , Decl <$> pure Nothing <*> QC.arbitrary
+ ]
+
+-- | 'module' module_identifier [list_of_ports] ';' { module_item } 'end_module'
+data ModDecl = ModDecl { _moduleId :: Identifier
+ , _modOutPorts :: [Port]
+ , _modInPorts :: [Port]
+ , _moduleItems :: [ModItem]
+ } deriving (Eq)
+
+makeLenses ''ModDecl
+
+modPortGen :: QC.Gen Port
+modPortGen = QC.oneof
+ [ Port Wire <$> positiveArb <*> QC.arbitrary
+ , Port <$> (Reg <$> QC.arbitrary) <*> positiveArb <*> QC.arbitrary
+ ]
+
+
+instance QC.Arbitrary ModDecl where
+ arbitrary = ModDecl <$> QC.arbitrary <*> QC.arbitrary
+ <*> QC.listOf1 modPortGen <*> QC.arbitrary
+
+-- | Description of the Verilog module.
+newtype Description = Description { _getDescription :: ModDecl }
+ deriving (Eq)
+
+makeLenses ''Description
+
+instance QC.Arbitrary Description where
+ arbitrary = Description <$> QC.arbitrary
+
+-- | The complete sourcetext for the Verilog module.
+newtype VerilogSrc = VerilogSrc { _getVerilogSrc :: [Description] }
+ deriving (Eq)
+
+makeLenses ''VerilogSrc
+
+instance Semigroup VerilogSrc where
+ VerilogSrc a <> VerilogSrc b = VerilogSrc $ a ++ b
+
+instance Monoid VerilogSrc where
+ mempty = VerilogSrc []
+
+instance QC.Arbitrary VerilogSrc where
+ arbitrary = VerilogSrc <$> QC.arbitrary
diff --git a/src/VeriFuzz/Verilog/Arbitrary.hs b/src/VeriFuzz/Verilog/Arbitrary.hs
new file mode 100644
index 0000000..1bcb727
--- /dev/null
+++ b/src/VeriFuzz/Verilog/Arbitrary.hs
@@ -0,0 +1,184 @@
+{-|
+Module : Test.VeriFuzz.Verilog.Arbitrary
+Description : Arbitrary instances for the AST.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : GPL-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Arbitrary instances for the AST.
+-}
+
+module Test.VeriFuzz.Verilog.Arbitrary where
+
+import Control.Monad (replicateM)
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Test.QuickCheck as QC
+import Test.VeriFuzz.Verilog.AST
+
+-- Generate Arbitrary instances for the AST
+
+positiveArb :: (QC.Arbitrary a, Ord a, Num a) => QC.Gen a
+positiveArb = QC.suchThat QC.arbitrary (>0)
+
+expr :: Int -> QC.Gen Expr
+expr 0 = QC.oneof
+ [ Id <$> QC.arbitrary
+ , Number <$> positiveArb <*> QC.arbitrary
+ , UnOp <$> QC.arbitrary <*> QC.arbitrary
+ -- , Str <$> QC.arbitrary
+ ]
+expr n
+ | n > 0 = QC.oneof
+ [ Id <$> QC.arbitrary
+ , Number <$> positiveArb <*> QC.arbitrary
+ , Concat <$> QC.listOf1 (subexpr 4)
+ , UnOp <$> QC.arbitrary <*> QC.arbitrary
+ -- , Str <$> QC.arbitrary
+ , BinOp <$> subexpr 2 <*> QC.arbitrary <*> subexpr 2
+ , Cond <$> subexpr 3 <*> subexpr 3 <*> subexpr 3
+ ]
+ | otherwise = expr 0
+ where
+ subexpr y = expr (n `div` y)
+
+statement :: Int -> QC.Gen Stmnt
+statement 0 = QC.oneof
+ [ BlockAssign <$> QC.arbitrary
+ , NonBlockAssign <$> QC.arbitrary
+ -- , StatCA <$> QC.arbitrary
+ , TaskEnable <$> QC.arbitrary
+ , SysTaskEnable <$> QC.arbitrary
+ ]
+statement n
+ | n > 0 = QC.oneof
+ [ TimeCtrl <$> QC.arbitrary <*> (Just <$> substat 2)
+ , SeqBlock <$> QC.listOf1 (substat 4)
+ , BlockAssign <$> QC.arbitrary
+ , NonBlockAssign <$> QC.arbitrary
+ -- , StatCA <$> QC.arbitrary
+ , TaskEnable <$> QC.arbitrary
+ , SysTaskEnable <$> QC.arbitrary
+ ]
+ | otherwise = statement 0
+ where
+ substat y = statement (n `div` y)
+
+modPortGen :: QC.Gen Port
+modPortGen = QC.oneof
+ [ Port Wire <$> positiveArb <*> QC.arbitrary
+ , Port <$> (Reg <$> QC.arbitrary) <*> positiveArb <*> QC.arbitrary
+ ]
+
+instance QC.Arbitrary Text where
+ arbitrary = T.pack <$> QC.arbitrary
+
+instance QC.Arbitrary Identifier where
+ arbitrary = do
+ l <- QC.choose (2, 10)
+ Identifier . T.pack <$> replicateM l (QC.elements ['a'..'z'])
+
+instance QC.Arbitrary BinaryOperator where
+ arbitrary = QC.elements
+ [ BinPlus
+ , BinMinus
+ , BinTimes
+ , BinDiv
+ , BinMod
+ , BinEq
+ , BinNEq
+ , BinCEq
+ , BinCNEq
+ , BinLAnd
+ , BinLOr
+ , BinLT
+ , BinLEq
+ , BinGT
+ , BinGEq
+ , BinAnd
+ , BinOr
+ , BinXor
+ , BinXNor
+ , BinXNorInv
+ , BinPower
+ , BinLSL
+ , BinLSR
+ , BinASL
+ , BinASR
+ ]
+
+instance QC.Arbitrary UnaryOperator where
+ arbitrary = QC.elements
+ [ UnPlus
+ , UnMinus
+ , UnNot
+ , UnAnd
+ , UnNand
+ , UnOr
+ , UnNor
+ , UnXor
+ , UnNxor
+ , UnNxorInv
+ ]
+
+instance QC.Arbitrary PortDir where
+ arbitrary = QC.elements [PortIn, PortOut, PortInOut]
+
+instance QC.Arbitrary PortType where
+ arbitrary = QC.oneof [pure Wire, Reg <$> QC.arbitrary]
+
+instance QC.Arbitrary Port where
+ arbitrary = Port <$> QC.arbitrary <*> positiveArb <*> QC.arbitrary
+
+instance QC.Arbitrary Delay where
+ arbitrary = Delay <$> positiveArb
+
+instance QC.Arbitrary Event where
+ arbitrary = EId <$> QC.arbitrary
+
+instance QC.Arbitrary ModConn where
+ arbitrary = ModConn <$> QC.arbitrary
+
+instance QC.Arbitrary ConstExpr where
+ arbitrary = ConstExpr <$> positiveArb
+
+instance QC.Arbitrary LVal where
+ arbitrary = QC.oneof [ RegId <$> QC.arbitrary
+ , RegExpr <$> QC.arbitrary <*> QC.arbitrary
+ , RegSize <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
+ ]
+
+instance QC.Arbitrary Assign where
+ arbitrary = Assign <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
+
+instance QC.Arbitrary Expr where
+ arbitrary = QC.sized expr
+
+instance QC.Arbitrary Stmnt where
+ arbitrary = QC.sized statement
+
+instance QC.Arbitrary ContAssign where
+ arbitrary = ContAssign <$> QC.arbitrary <*> QC.arbitrary
+
+instance QC.Arbitrary Task where
+ arbitrary = Task <$> QC.arbitrary <*> QC.arbitrary
+
+instance QC.Arbitrary ModItem where
+ arbitrary = QC.oneof [ ModCA <$> QC.arbitrary
+ , ModInst <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
+ , Initial <$> QC.arbitrary
+ , Always <$> (EventCtrl <$> QC.arbitrary <*> QC.arbitrary)
+ , Decl <$> pure Nothing <*> QC.arbitrary
+ ]
+
+instance QC.Arbitrary ModDecl where
+ arbitrary = ModDecl <$> QC.arbitrary <*> QC.arbitrary
+ <*> QC.listOf1 modPortGen <*> QC.arbitrary
+
+instance QC.Arbitrary Description where
+ arbitrary = Description <$> QC.arbitrary
+
+instance QC.Arbitrary VerilogSrc where
+ arbitrary = VerilogSrc <$> QC.arbitrary
diff --git a/src/VeriFuzz/Verilog/CodeGen.hs b/src/VeriFuzz/Verilog/CodeGen.hs
new file mode 100644
index 0000000..d97c8b9
--- /dev/null
+++ b/src/VeriFuzz/Verilog/CodeGen.hs
@@ -0,0 +1,315 @@
+{-|
+Module : VeriFuzz.Verilog.CodeGen
+Description : Code generation for Verilog AST.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+This module generates the code from the Verilog AST defined in
+"VeriFuzz.Verilog.AST".
+-}
+
+module VeriFuzz.Verilog.CodeGen where
+
+import Control.Lens
+import Data.Foldable (fold)
+import Data.Maybe (isNothing)
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.Text.IO as T
+import Numeric (showHex)
+import VeriFuzz.Internal.Shared
+import VeriFuzz.Verilog.AST
+
+-- | Inserts commas between '[Text]' and except the last one.
+comma :: [Text] -> Text
+comma = T.intercalate ", "
+
+-- | Show function for 'Text'
+showT :: (Show a) => a -> Text
+showT = T.pack . show
+
+-- | Map a 'Maybe Stmnt' to 'Text'. If it is 'Just stmnt', the generated
+-- statements are returned. If it is 'Nothing', then @;\n@ is returned.
+defMap :: Maybe Stmnt -> Text
+defMap = maybe ";\n" genStmnt
+
+-- | Convert the 'VerilogSrc' type to 'Text' so that it can be rendered.
+genVerilogSrc :: VerilogSrc -> Text
+genVerilogSrc source =
+ fold $ genDescription <$> source ^. getVerilogSrc
+
+-- | Generate the 'Description' to 'Text'.
+genDescription :: Description -> Text
+genDescription desc =
+ genModuleDecl $ desc ^. getDescription
+
+-- | Generate the 'ModDecl' for a module and convert it to 'Text'.
+genModuleDecl :: ModDecl -> Text
+genModuleDecl mod =
+ "module " <> mod ^. moduleId . getIdentifier
+ <> ports <> ";\n"
+ <> modItems
+ <> "endmodule\n"
+ where
+ ports
+ | noIn && noOut = ""
+ | otherwise = "(" <> comma (genModPort <$> outIn) <> ")"
+ modItems = fold $ genModuleItem <$> mod ^. moduleItems
+ noOut = null $ mod ^. modOutPorts
+ noIn = null $ mod ^. modInPorts
+ outIn = (mod ^. modOutPorts) ++ (mod ^. modInPorts)
+
+-- | Conversts 'Port' to 'Text' for the module list, which means it only
+-- generates a list of identifiers.
+genModPort :: Port -> Text
+genModPort port = port ^. portName . getIdentifier
+
+-- | Generate the 'Port' description.
+genPort :: Port -> Text
+genPort port =
+ t <> size <> name
+ where
+ t = (<>" ") . genPortType $ port ^. portType
+ size
+ | port ^. portSize > 1 = "[" <> showT (port ^. portSize - 1) <> ":0] "
+ | otherwise = ""
+ name = port ^. portName . getIdentifier
+
+-- | Convert the 'PortDir' type to 'Text'.
+genPortDir :: PortDir -> Text
+genPortDir PortIn = "input"
+genPortDir PortOut = "output"
+genPortDir PortInOut = "inout"
+
+-- | Generate a 'ModItem'.
+genModuleItem :: ModItem -> Text
+genModuleItem (ModCA ca) = genContAssign ca
+genModuleItem (ModInst (Identifier id) (Identifier name) conn) =
+ id <> " " <> name <> "(" <> comma (genExpr . _modConn <$> conn) <> ")" <> ";\n"
+genModuleItem (Initial stat) = "initial " <> genStmnt stat
+genModuleItem (Always stat) = "always " <> genStmnt stat
+genModuleItem (Decl dir port) =
+ (maybe "" makePort dir) <> genPort port <> ";\n"
+ where
+ makePort = (<>" ") . genPortDir
+
+-- | Generate continuous assignment
+genContAssign :: ContAssign -> Text
+genContAssign (ContAssign val e) =
+ "assign " <> name <> " = " <> expr <> ";\n"
+ where
+ name = val ^. getIdentifier
+ expr = genExpr e
+
+-- | Generate 'Expr' to 'Text'.
+genExpr :: Expr -> Text
+genExpr (BinOp exprRhs bin exprLhs) =
+ "(" <> genExpr exprRhs <> genBinaryOperator bin <> genExpr exprLhs <> ")"
+genExpr (Number s n) =
+ showT s <> "'h" <> T.pack (showHex n "")
+genExpr (Id i) = i ^. getIdentifier
+genExpr (Concat c) = "{" <> comma (genExpr <$> c) <> "}"
+genExpr (UnOp u e) =
+ "(" <> genUnaryOperator u <> genExpr e <> ")"
+genExpr (Cond l t f) =
+ "(" <> genExpr l <> " ? " <> genExpr t <> " : " <> genExpr f <> ")"
+genExpr (Str t) = "\"" <> t <> "\""
+
+-- | Convert 'BinaryOperator' to 'Text'.
+genBinaryOperator :: BinaryOperator -> Text
+genBinaryOperator BinPlus = " + "
+genBinaryOperator BinMinus = " - "
+genBinaryOperator BinTimes = " * "
+genBinaryOperator BinDiv = " / "
+genBinaryOperator BinMod = " % "
+genBinaryOperator BinEq = " == "
+genBinaryOperator BinNEq = " != "
+genBinaryOperator BinCEq = " === "
+genBinaryOperator BinCNEq = " !== "
+genBinaryOperator BinLAnd = " && "
+genBinaryOperator BinLOr = " || "
+genBinaryOperator BinLT = " < "
+genBinaryOperator BinLEq = " <= "
+genBinaryOperator BinGT = " > "
+genBinaryOperator BinGEq = " >= "
+genBinaryOperator BinAnd = " & "
+genBinaryOperator BinOr = " | "
+genBinaryOperator BinXor = " ^ "
+genBinaryOperator BinXNor = " ^~ "
+genBinaryOperator BinXNorInv = " ~^ "
+genBinaryOperator BinPower = " ** "
+genBinaryOperator BinLSL = " << "
+genBinaryOperator BinLSR = " >> "
+genBinaryOperator BinASL = " <<< "
+genBinaryOperator BinASR = " >>> "
+
+-- | Convert 'UnaryOperator' to 'Text'.
+genUnaryOperator :: UnaryOperator -> Text
+genUnaryOperator UnPlus = "+"
+genUnaryOperator UnMinus = "-"
+genUnaryOperator UnNot = "!"
+genUnaryOperator UnAnd = "&"
+genUnaryOperator UnNand = "~&"
+genUnaryOperator UnOr = "|"
+genUnaryOperator UnNor = "~|"
+genUnaryOperator UnXor = "^"
+genUnaryOperator UnNxor = "~^"
+genUnaryOperator UnNxorInv = "^~"
+
+-- | Generate verilog code for an 'Event'.
+genEvent :: Event -> Text
+genEvent (EId id) = "@(" <> id ^. getIdentifier <> ")"
+genEvent (EExpr expr) = "@(" <> genExpr expr <> ")"
+genEvent EAll = "@*"
+
+-- | Generates verilog code for a 'Delay'.
+genDelay :: Delay -> Text
+genDelay (Delay i) = "#" <> showT i
+
+-- | Generate the verilog code for an 'LVal'.
+genLVal :: LVal -> Text
+genLVal (RegId id) = id ^. getIdentifier
+genLVal (RegExpr id expr) =
+ id ^. getIdentifier <> " [" <> genExpr expr <> "]"
+genLVal (RegSize id msb lsb) =
+ id ^. getIdentifier <> " [" <> genConstExpr msb <> ":" <> genConstExpr lsb <> "]"
+genLVal (RegConcat e) =
+ "{" <> comma (genExpr <$> e) <> "}"
+
+genConstExpr :: ConstExpr -> Text
+genConstExpr (ConstExpr num) = showT num
+
+genPortType :: PortType -> Text
+genPortType Wire = "wire"
+genPortType (Reg signed)
+ | signed = "reg signed"
+ | otherwise = "reg"
+
+genAssign :: Text -> Assign -> Text
+genAssign op (Assign r d e) =
+ genLVal r <> op <> maybe "" genDelay d <> genExpr e
+
+genStmnt :: Stmnt -> Text
+genStmnt (TimeCtrl d stat) = genDelay d <> " " <> defMap stat
+genStmnt (EventCtrl e stat) = genEvent e <> " " <> defMap stat
+genStmnt (SeqBlock s) =
+ "begin\n" <> fold (genStmnt <$> s) <> "end\n"
+genStmnt (BlockAssign a) = genAssign " = " a <> ";\n"
+genStmnt (NonBlockAssign a) = genAssign " <= " a <> ";\n"
+genStmnt (StatCA a) = genContAssign a
+genStmnt (TaskEnable task) = genTask task <> ";\n"
+genStmnt (SysTaskEnable task) = "$" <> genTask task <> ";\n"
+
+genTask :: Task -> Text
+genTask (Task name expr)
+ | null expr = id
+ | otherwise = id <> "(" <> comma (genExpr <$> expr) <> ")"
+ where
+ id = name ^. getIdentifier
+
+-- | Render the 'Text' to 'IO'. This is equivalent to 'putStrLn'.
+render :: Text -> IO ()
+render = T.putStrLn
+
+-- Instances
+
+instance Source Task where
+ genSource = genTask
+
+instance Source Stmnt where
+ genSource = genStmnt
+
+instance Source PortType where
+ genSource = genPortType
+
+instance Source ConstExpr where
+ genSource = genConstExpr
+
+instance Source LVal where
+ genSource = genLVal
+
+instance Source Delay where
+ genSource = genDelay
+
+instance Source Event where
+ genSource = genEvent
+
+instance Source UnaryOperator where
+ genSource = genUnaryOperator
+
+instance Source Expr where
+ genSource = genExpr
+
+instance Source ContAssign where
+ genSource = genContAssign
+
+instance Source ModItem where
+ genSource = genModuleItem
+
+instance Source PortDir where
+ genSource = genPortDir
+
+instance Source Port where
+ genSource = genPort
+
+instance Source ModDecl where
+ genSource = genModuleDecl
+
+instance Source Description where
+ genSource = genDescription
+
+instance Source VerilogSrc where
+ genSource = genVerilogSrc
+
+-- Show instances
+
+instance Show Task where
+ show = T.unpack . genTask
+
+instance Show Stmnt where
+ show = T.unpack . genStmnt
+
+instance Show PortType where
+ show = T.unpack . genPortType
+
+instance Show ConstExpr where
+ show = T.unpack . genConstExpr
+
+instance Show LVal where
+ show = T.unpack . genLVal
+
+instance Show Delay where
+ show = T.unpack . genDelay
+
+instance Show Event where
+ show = T.unpack . genEvent
+
+instance Show UnaryOperator where
+ show = T.unpack . genUnaryOperator
+
+instance Show Expr where
+ show = T.unpack . genExpr
+
+instance Show ContAssign where
+ show = T.unpack . genContAssign
+
+instance Show ModItem where
+ show = T.unpack . genModuleItem
+
+instance Show PortDir where
+ show = T.unpack . genPortDir
+
+instance Show Port where
+ show = T.unpack . genPort
+
+instance Show ModDecl where
+ show = T.unpack . genModuleDecl
+
+instance Show Description where
+ show = T.unpack . genDescription
+
+instance Show VerilogSrc where
+ show = T.unpack . genVerilogSrc
diff --git a/src/VeriFuzz/Verilog/Helpers.hs b/src/VeriFuzz/Verilog/Helpers.hs
new file mode 100644
index 0000000..0204379
--- /dev/null
+++ b/src/VeriFuzz/Verilog/Helpers.hs
@@ -0,0 +1,75 @@
+{-|
+Module : VeriFuzz.Verilog.Helpers
+Description : Defaults and common functions.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Defaults and common functions.
+-}
+
+module VeriFuzz.Verilog.Helpers where
+
+import Control.Lens
+import Data.Text (Text)
+import qualified Data.Text
+import VeriFuzz.Verilog.AST
+
+regDecl :: Identifier -> ModItem
+regDecl = Decl Nothing . Port (Reg False) 1
+
+wireDecl :: Identifier -> ModItem
+wireDecl = Decl Nothing . Port Wire 1
+
+modConn :: Identifier -> ModConn
+modConn = ModConn . Id
+
+-- | Create an empty module.
+emptyMod :: ModDecl
+emptyMod = ModDecl "" [] [] []
+
+-- | Set a module name for a module declaration.
+setModName :: Text -> ModDecl -> ModDecl
+setModName str = moduleId .~ Identifier str
+
+-- | Add a input port to the module declaration.
+addModPort :: Port -> ModDecl -> ModDecl
+addModPort port = modInPorts %~ (:) port
+
+addDescription :: Description -> VerilogSrc -> VerilogSrc
+addDescription desc = getVerilogSrc %~ (:) desc
+
+testBench :: ModDecl
+testBench =
+ ModDecl "main" [] []
+ [ regDecl "a"
+ , regDecl "b"
+ , wireDecl "c"
+ , ModInst "and" "and_gate"
+ [ modConn "c"
+ , modConn "a"
+ , modConn "b"
+ ]
+ , Initial $ SeqBlock
+ [ BlockAssign . Assign (RegId "a") Nothing $ Number 1 1
+ , BlockAssign . Assign (RegId "b") Nothing $ Number 1 1
+ -- , TimeCtrl (Delay 1) . Just . SysTaskEnable $ Task "display"
+ -- [ Str "%d & %d = %d"
+ -- , PrimExpr $ PrimId "a"
+ -- , PrimExpr $ PrimId "b"
+ -- , PrimExpr $ PrimId "c"
+ -- ]
+ -- , SysTaskEnable $ Task "finish" []
+ ]
+ ]
+
+addTestBench :: VerilogSrc -> VerilogSrc
+addTestBench = addDescription $ Description testBench
+
+defaultPort :: Identifier -> Port
+defaultPort = Port Wire 1
+
+portToExpr :: Port -> Expr
+portToExpr (Port _ _ id) = Id id
diff --git a/src/VeriFuzz/Verilog/Mutate.hs b/src/VeriFuzz/Verilog/Mutate.hs
new file mode 100644
index 0000000..501d217
--- /dev/null
+++ b/src/VeriFuzz/Verilog/Mutate.hs
@@ -0,0 +1,148 @@
+{-|
+Module : VeriFuzz.Verilog.Mutation
+Description : Functions to mutate the Verilog AST.
+Copyright : (c) 2018-2019, Yann Herklotz Grave
+License : BSD-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Functions to mutate the Verilog AST from "VeriFuzz.Verilog.AST" to generate
+more random patterns, such as nesting wires instead of creating new ones.
+-}
+
+module VeriFuzz.Verilog.Mutate where
+
+import Control.Lens
+import Data.Maybe (catMaybes, fromMaybe)
+import VeriFuzz.Internal.Gen
+import VeriFuzz.Internal.Shared
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.CodeGen
+
+-- | Return if the 'Identifier' is in a 'ModDecl'.
+inPort :: Identifier -> ModDecl -> Bool
+inPort id mod = inInput
+ where
+ inInput = any (\a -> a ^. portName == id) $ mod ^. modInPorts ++ mod ^. modOutPorts
+
+-- | Find the last assignment of a specific wire/reg to an expression, and
+-- returns that expression.
+findAssign :: Identifier -> [ModItem] -> Maybe Expr
+findAssign id items =
+ safe last . catMaybes $ isAssign <$> items
+ where
+ isAssign (ModCA (ContAssign val expr))
+ | val == id = Just expr
+ | otherwise = Nothing
+ isAssign _ = Nothing
+
+-- | Transforms an expression by replacing an Identifier with an
+-- expression. This is used inside 'transformOf' and 'traverseExpr' to replace
+-- the 'Identifier' recursively.
+idTrans :: Identifier -> Expr -> Expr -> Expr
+idTrans i expr (Id id)
+ | id == i = expr
+ | otherwise = Id id
+idTrans _ _ e = e
+
+-- | Replaces the identifier recursively in an expression.
+replace :: Identifier -> Expr -> Expr -> Expr
+replace = (transformOf traverseExpr .) . idTrans
+
+-- | Nest expressions for a specific 'Identifier'. If the 'Identifier' is not found,
+-- the AST is not changed.
+--
+-- This could be improved by instead of only using the last assignment to the
+-- wire that one finds, to use the assignment to the wire before the current
+-- expression. This would require a different approach though.
+nestId :: Identifier -> ModDecl -> ModDecl
+nestId id mod
+ | not $ inPort id mod =
+ let expr = fromMaybe def . findAssign id $ mod ^. moduleItems
+ in mod & get %~ replace id expr
+ | otherwise = mod
+ where
+ get = moduleItems . traverse . _ModCA . contAssignExpr
+ def = Id id
+
+-- | Replaces an identifier by a expression in all the module declaration.
+nestSource :: Identifier -> VerilogSrc -> VerilogSrc
+nestSource id src =
+ src & getVerilogSrc . traverse . getDescription %~ nestId id
+
+-- | Nest variables in the format @w[0-9]*@ up to a certain number.
+nestUpTo :: Int -> VerilogSrc -> VerilogSrc
+nestUpTo i src =
+ foldl (flip nestSource) src $ Identifier . fromNode <$> [1..i]
+
+allVars :: ModDecl -> [Identifier]
+allVars mod =
+ (mod ^.. modOutPorts . traverse . portName) ++ (mod ^.. modInPorts . traverse . portName)
+-- $setup
+-- >>> let mod = (ModDecl (Identifier "m") [Port Wire 5 (Identifier "y")] [Port Wire 5 "x"] [])
+-- >>> let main = (ModDecl "main" [] [] [])
+
+-- | Add a Module Instantiation using 'ModInst' from the first module passed to
+-- it to the body of the second module. It first has to make all the inputs into
+-- @reg@.
+--
+-- >>> instantiateMod mod main
+-- module main;
+-- wire [4:0] y;
+-- reg [4:0] x;
+-- m m1(y, x);
+-- endmodule
+-- <BLANKLINE>
+instantiateMod :: ModDecl -> ModDecl -> ModDecl
+instantiateMod mod main =
+ main & moduleItems %~ ((out ++ regIn ++ [inst])++)
+ where
+ out = Decl Nothing <$> mod ^. modOutPorts
+ regIn = Decl Nothing <$> (mod ^. modInPorts & traverse . portType .~ Reg False)
+ inst = ModInst (mod ^. moduleId) (mod ^. moduleId <> (Identifier . showT $ count+1)) conns
+ count = length . filter (==mod ^. moduleId) $ main ^.. moduleItems . traverse . modInstId
+ conns = ModConn . Id <$> allVars mod
+
+-- | Instantiate without adding wire declarations. It also does not count the
+-- current instantiations of the same module.
+--
+-- >>> instantiateMod_ mod main
+-- m m(y, x);
+-- <BLANKLINE>
+instantiateMod_ :: ModDecl -> ModItem
+instantiateMod_ mod =
+ ModInst (mod ^. moduleId) (mod ^. moduleId) conns
+ where
+ conns = ModConn . Id <$>
+ (mod ^.. modOutPorts . traverse . portName) ++ (mod ^.. modInPorts . traverse . portName)
+
+-- | Initialise all the inputs and outputs to a module.
+--
+-- >>> initMod mod
+-- module m(y, x);
+-- output wire [4:0] y;
+-- input wire [4:0] x;
+-- endmodule
+-- <BLANKLINE>
+initMod :: ModDecl -> ModDecl
+initMod mod = mod & moduleItems %~ ((out ++ inp)++)
+ where
+ out = Decl (Just PortOut) <$> (mod ^. modOutPorts)
+ inp = Decl (Just PortIn) <$> (mod ^. modInPorts)
+
+makeIdFrom :: (Show a) => a -> Identifier -> Identifier
+makeIdFrom a i =
+ (i<>) . Identifier . ("_"<>) $ showT a
+
+-- | Make top level module for equivalence verification. Also takes in how many
+-- modules to instantiate.
+makeTop :: Int -> ModDecl -> ModDecl
+makeTop i m =
+ ModDecl (m ^. moduleId) ys (m ^. modInPorts) modItems
+ where
+ ys = Port Wire 90 . (flip makeIdFrom) "y" <$> [1..i]
+ modItems = instantiateMod_ . modN <$> [1..i]
+ modN n = m
+ & moduleId %~ makeIdFrom n
+ & modOutPorts .~ [Port Wire 90 (makeIdFrom n "y")]