aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorYann Herklotz <ymherklotz@gmail.com>2018-12-15 20:18:22 +0000
committerYann Herklotz <ymherklotz@gmail.com>2018-12-15 20:18:22 +0000
commitaf7f1a5522d90bccfb16ca0d7f9f8726f419a113 (patch)
treed035c78151738f82ef78259455a2c34df589f558 /src
parente74aa25c176df5dd1291b8ae3ff883ef67cb3f04 (diff)
downloadverismith-af7f1a5522d90bccfb16ca0d7f9f8726f419a113.tar.gz
verismith-af7f1a5522d90bccfb16ca0d7f9f8726f419a113.zip
Add AST generation
Diffstat (limited to 'src')
-rw-r--r--src/Test/VeriFuzz/Graph/ASTGen.hs47
1 files changed, 47 insertions, 0 deletions
diff --git a/src/Test/VeriFuzz/Graph/ASTGen.hs b/src/Test/VeriFuzz/Graph/ASTGen.hs
new file mode 100644
index 0000000..f481c24
--- /dev/null
+++ b/src/Test/VeriFuzz/Graph/ASTGen.hs
@@ -0,0 +1,47 @@
+{-|
+Module : Test.VeriFuzz.Graph.ASTGen
+Description : Generates the AST from the graph directly.
+Copyright : (c) Yann Herklotz Grave 2018
+License : GPL-3
+Maintainer : ymherklotz@gmail.com
+Stability : experimental
+Portability : POSIX
+
+Generates the AST from the graph directly.
+-}
+
+{-# LANGUAGE OverloadedStrings #-}
+
+module Test.VeriFuzz.Graph.ASTGen where
+
+import qualified Data.Graph.Inductive as G
+import qualified Data.Text as T
+import Test.VeriFuzz.Circuit
+import Test.VeriFuzz.VerilogAST
+
+fromNode :: G.Node -> Identifier
+fromNode node = Identifier . T.pack $ "w" <> show node
+
+filterGr :: (G.Graph gr) => gr n e -> (G.Node -> Bool) -> [G.Node]
+filterGr graph f =
+ filter f $ G.nodes graph
+
+genPortsAST :: Circuit -> [Port]
+genPortsAST c = ((Port Input . fromNode) <$> inp) ++ ((Port Output) . fromNode <$> out)
+ where
+ zero fun1 fun2 n = fun1 graph n == 0 && fun2 graph n /= 0
+ inp = filterGr graph $ zero G.indeg G.outdeg
+ out = filterGr graph $ zero G.outdeg G.indeg
+ graph = getCircuit c
+
+genModuleDeclAST :: Circuit -> ModuleDecl
+genModuleDeclAST c =
+ ModuleDecl id ports items
+ where
+ id = Identifier "gen_module"
+ ports = genPortsAST c
+ items = []
+
+generateAST :: Circuit -> SourceText
+generateAST c =
+ SourceText [Description $ genModuleDeclAST c]