aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorYann Herklotz <ymherklotz@gmail.com>2018-11-16 21:17:29 +0000
committerYann Herklotz <ymherklotz@gmail.com>2018-11-16 21:17:29 +0000
commit9bb2f6d5a8815ec10f83e917395ac511a153e6f2 (patch)
treeb19107667d7b7ec57f55405e2c6cef5facb7be01 /src
parent339536b17935a622ba96dc764ae643a1ac8bf82d (diff)
downloadverismith-9bb2f6d5a8815ec10f83e917395ac511a153e6f2.tar.gz
verismith-9bb2f6d5a8815ec10f83e917395ac511a153e6f2.zip
Basic generation with errors
Diffstat (limited to 'src')
-rw-r--r--src/Main.hs2
-rw-r--r--src/Test/VeriFuzz/CodeGen.hs26
-rw-r--r--src/Test/VeriFuzz/Graph/Random.hs2
3 files changed, 24 insertions, 6 deletions
diff --git a/src/Main.hs b/src/Main.hs
index fd07ef1..d41d46b 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -15,5 +15,5 @@ main :: IO ()
--main = sample (arbitrary :: Gen (Circuit Input))
main = do
gr <- randomDAG 100 :: IO (Gr Gate ())
- _ <- runGraphviz (graphToDot quickParams $ emap (const "") gr) Png "output.png"
+-- _ <- runGraphviz (graphToDot quickParams $ emap (const "") gr) Png "output.png"
T.putStrLn $ generate gr
diff --git a/src/Test/VeriFuzz/CodeGen.hs b/src/Test/VeriFuzz/CodeGen.hs
index a743f0f..62a604c 100644
--- a/src/Test/VeriFuzz/CodeGen.hs
+++ b/src/Test/VeriFuzz/CodeGen.hs
@@ -2,8 +2,9 @@
module Test.VeriFuzz.CodeGen where
-import Data.Graph.Inductive (Graph, LNode, Node, indeg, nodes, outdeg,
- pre)
+import Data.Graph.Inductive (Graph, LNode, Node, indeg, labNodes,
+ nodes, outdeg, pre)
+import Data.Maybe (fromMaybe)
import Data.Text (Text, empty, pack)
import Test.VeriFuzz.Types
@@ -17,16 +18,32 @@ filterGr graph f =
fromList :: [Text] -> Text
fromList = foldl mappend empty
+safeTail :: [a] -> Maybe [a]
+safeTail [] = Nothing
+safeTail l = Just $ tail l
+
+safeHead :: [a] -> Maybe a
+safeHead [] = Nothing
+safeHead l = Just $ head l
+
toOperator :: Gate -> Text
toOperator And = " & "
toOperator Or = " | "
toOperator Xor = " ^ "
+statList :: Gate -> [Node] -> Maybe Text
+statList g n = toStr <$> safeTail n
+ where
+ toStr = fromList . map ((<> toOperator g) . fromNode)
+
+lastEl :: [Node] -> Maybe Text
+lastEl n = fromNode <$> safeHead n
+
toStatement :: (Graph gr) => gr Gate e -> LNode Gate -> Text
toStatement graph (n, g) =
- fromNode n <> " = " <> connNodes <> ";\n"
+ fromMaybe empty $ Just " assign " <> Just (fromNode n) <> Just " = " <> statList g nodeL <> lastEl nodeL <> Just ";\n"
where
- connNodes = fromList . map ((<> toOperator g) . fromNode) $ pre graph n
+ nodeL = pre graph n
generate :: (Graph gr) => gr Gate e -> Text
generate graph =
@@ -34,6 +51,7 @@ generate graph =
<> fromList (imap " input wire " ",\n" inp)
<> fromList (imap " output wire " ",\n" out)
<> ");\n"
+ <> fromList (map (toStatement graph) (labNodes graph))
<> "endmodule\n\nmodule main;\n initial\n begin\n "
<> "$display(\"Hello, world\");\n $finish;\n "
<> "end\nendmodule"
diff --git a/src/Test/VeriFuzz/Graph/Random.hs b/src/Test/VeriFuzz/Graph/Random.hs
index e14d73e..9aa849b 100644
--- a/src/Test/VeriFuzz/Graph/Random.hs
+++ b/src/Test/VeriFuzz/Graph/Random.hs
@@ -20,6 +20,6 @@ randomDAG :: (Arbitrary l, Arbitrary e, Graph gr)
randomDAG n = do
list <- generate . infiniteListOf $ arbitrary
l <- generate . infiniteListOf $ arbitraryEdge n
- return . mkGraph (nodes list) $ take (5*n) l
+ return . mkGraph (nodes list) $ take (10*n) l
where
nodes l = zip [0..n] $ take n l