aboutsummaryrefslogtreecommitdiffstats
path: root/src/Test/VeriFuzz/Graph/ASTGen.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Test/VeriFuzz/Graph/ASTGen.hs')
-rw-r--r--src/Test/VeriFuzz/Graph/ASTGen.hs29
1 files changed, 21 insertions, 8 deletions
diff --git a/src/Test/VeriFuzz/Graph/ASTGen.hs b/src/Test/VeriFuzz/Graph/ASTGen.hs
index fffb3f8..97b6c1c 100644
--- a/src/Test/VeriFuzz/Graph/ASTGen.hs
+++ b/src/Test/VeriFuzz/Graph/ASTGen.hs
@@ -14,16 +14,20 @@ Generates the AST from the graph directly.
module Test.VeriFuzz.Graph.ASTGen where
-import qualified Data.Graph.Inductive (LNode, Node)
+import Data.Graph.Inductive (LNode, Node)
import qualified Data.Graph.Inductive as G
+import Data.Maybe (catMaybes)
import qualified Data.Text as T
import Test.VeriFuzz.Circuit
import Test.VeriFuzz.Internal.Gen
import Test.VeriFuzz.VerilogAST
+-- | Converts a 'Node' 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
@@ -31,18 +35,27 @@ fromGate Xor = BinXor
genPortsAST :: Circuit -> [Port]
genPortsAST c =
- ((Port Input . frNode) <$> inp) ++ ((Port Output) . frNode <$> out)
+ (Port Input . frNode <$> inp) ++ (Port Output . frNode <$> out)
where
inp = inputs graph
out = outputs graph
graph = getCircuit c
-genAssignExpr :: Gate -> [Node] -> Expression
-genAssignExpr g ns = (error "FIXME: Not yet done")
+-- | Generates the nested expression AST, so that it can then generate the
+-- assignment expressions.
+genAssignExpr :: Gate -> [Node] -> Maybe Expression
+genAssignExpr g [] = Nothing
+genAssignExpr g (n:[]) = Just . PrimExpr . PrimId $ frNode n
+genAssignExpr g (n:ns) = OpExpr wire op <$> genAssignExpr g ns
+ where
+ wire = PrimExpr . PrimId $ frNode n
+ op = fromGate g
-genContAssignAST :: Circuit -> LNode Gate -> ContAssign
-genContAssignAST c (n, g) =
- ContAssign name $ genAssignExpr g nodes
+-- | 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 ContAssign
+genContAssignAST c (n, g) = ContAssign name <$> genAssignExpr g nodes
where
gr = getCircuit c
nodes = G.pre gr n
@@ -50,7 +63,7 @@ genContAssignAST c (n, g) =
genAssignAST :: Circuit -> [ContAssign]
genAssignAST c =
- nodes
+ catMaybes $ genContAssignAST c <$> nodes
where
gr = getCircuit c
nodes = G.labNodes gr