aboutsummaryrefslogtreecommitdiffstats
path: root/src/Test/VeriFuzz/Graph/ASTGen.hs
blob: 781bbb9a83d1eb9819aa89eb0576da246afbff68 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
{-|
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

fromGate :: Gate -> BinaryOperator
fromGate And = BinAnd
fromGate Or  = BinOr
fromGate Xor = BinXor

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

genContAssignAST :: Circuit -> G.LNode Gate -> ContAssign
genContAssignAST c g =
  where
    gr = getCircuit c
    nodes = pre gr $ fst g

genAssignAST :: Circuit -> [ContAssign]
genAssignAST c =
  nodes
  where
    gr = getCircuit c
    nodes = G.labNodes gr

genModuleDeclAST :: Circuit -> ModuleDecl
genModuleDeclAST c =
  ModuleDecl id ports items
  where
    id = Identifier "gen_module"
    ports = genPortsAST c
    items = Assign <$> genAssignAST c

generateAST :: Circuit -> SourceText
generateAST c =
  SourceText [Description $ genModuleDeclAST c]