aboutsummaryrefslogtreecommitdiffstats
path: root/src/Test/VeriFuzz/VerilogAST.hs
blob: 5fdb9005cc546d8d7cc64ce86f5c8d6b92998022 (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
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell   #-}

module Test.VeriFuzz.VerilogAST where

import           Control.Lens
import           Data.Text    as T
import           Data.Text    (Text)

newtype Identifier = Identifier { _getIdentifier :: Text }
                   deriving (Show)
makeLenses ''Identifier

data Number = Number { _numSize :: Int
                     , _numVal  :: Int
                     } deriving (Show)
makeLenses ''Number

data BinaryOperator = BinAnd
                    | BinOr
                    | BinXor
                    deriving (Show)
makeLenses ''BinaryOperator

data UnaryOperator = UnNot
                   | UnMinus
                   deriving (Show)
makeLenses ''UnaryOperator

data Primary = PrimNum Number
             | PrimId Identifier
             deriving (Show)
makeLenses ''Primary

data Expression = PrimExpr Primary
                | UnPrimExpr { _exprUnOp :: UnaryOperator
                             , _exprPrim :: Primary
                             }
                | OpExpr { _exprLhs   :: Expression
                         , _exprBinOp :: BinaryOperator
                         , _exprRhs   :: Expression
                         }
                | CondExpr { _exprCond  :: Expression
                           , _exprTrue  :: Expression
                           , _exprFalse :: Expression
                           }
                deriving (Show)
makeLenses ''Expression

data ContAssign = ContAssign { _contAssignNetLVal :: Identifier
                             , _contAssignExpr    :: Expression
                             } deriving (Show)
makeLenses ''ContAssign

data PortDir = Input
             | Output
             | InOut
             deriving (Show)
makeLenses ''PortDir

data Port = Port { _portName :: Identifier
                 , _portDir  :: PortDir
                 } deriving (Show)
makeLenses ''Port

newtype ModuleItem = Assign ContAssign
                   deriving (Show)
makeLenses ''ModuleItem

-- | 'module' module_identifier [list_of_ports] ';' { module_item } 'end_module'
data ModuleDecl = ModuleDecl { _moduleId    :: Identifier
                             , _modPorts    :: [Port]
                             , _moduleItems :: [ModuleItem]
                             } deriving (Show)
makeLenses ''ModuleDecl

newtype Description = Description { _getDescription :: ModuleDecl }
                    deriving (Show)
makeLenses ''Description

newtype SourceText = SourceText { _getSourceText :: [Description] }
                   deriving (Show)
makeLenses ''SourceText

numExpr :: Int -> Int -> Expression
numExpr = ((PrimExpr . PrimNum) .) . Number

emptyMod :: ModuleDecl
emptyMod = ModuleDecl (Identifier "") [] []

setModName :: Text -> ModuleDecl -> ModuleDecl
setModName str = moduleId .~ Identifier str

addModPort :: Port -> ModuleDecl -> ModuleDecl
addModPort port = modPorts %~ ((:) port)