aboutsummaryrefslogtreecommitdiffstats
path: root/src/Test/VeriFuzz/Verilog
diff options
context:
space:
mode:
authorYann Herklotz <ymherklotz@gmail.com>2019-01-10 15:49:13 +0000
committerYann Herklotz <ymherklotz@gmail.com>2019-01-10 15:49:13 +0000
commitdac34f6ff5c46f11fe6c548b92a02ebf4f10d7e9 (patch)
treee51f51b4e82f3c764bcba88725e20e4fb10284da /src/Test/VeriFuzz/Verilog
parent3f1190cd7fc873449a1fd430386aa4b773d010ac (diff)
downloadverismith-dac34f6ff5c46f11fe6c548b92a02ebf4f10d7e9.tar.gz
verismith-dac34f6ff5c46f11fe6c548b92a02ebf4f10d7e9.zip
Rename files out of the module
Diffstat (limited to 'src/Test/VeriFuzz/Verilog')
-rw-r--r--src/Test/VeriFuzz/Verilog/AST.hs461
-rw-r--r--src/Test/VeriFuzz/Verilog/Arbitrary.hs184
-rw-r--r--src/Test/VeriFuzz/Verilog/CodeGen.hs315
-rw-r--r--src/Test/VeriFuzz/Verilog/Helpers.hs75
-rw-r--r--src/Test/VeriFuzz/Verilog/Mutate.hs148
5 files changed, 0 insertions, 1183 deletions
diff --git a/src/Test/VeriFuzz/Verilog/AST.hs b/src/Test/VeriFuzz/Verilog/AST.hs
deleted file mode 100644
index 63b1923..0000000
--- a/src/Test/VeriFuzz/Verilog/AST.hs
+++ /dev/null
@@ -1,461 +0,0 @@
-{-|
-Module : VeriFuzz.Verilog.AST
-Description : Definition of the Verilog AST types.
-Copyright : (c) 2018-2019, Yann Herklotz Grave
-License : BSD-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Poratbility : POSIX
-
-Defines the types to build a Verilog AST.
--}
-
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-{-# LANGUAGE TemplateHaskell #-}
-
-module VeriFuzz.Verilog.AST where
-
-import Control.Lens (makeLenses, (^.))
-import Data.String (IsString, fromString)
-import Data.Text (Text)
-import qualified Data.Text as T
-import Data.Traversable (sequenceA)
-import qualified QuickCheck as QC
-
--- | 'Source' class which determines that source code is able to be generated
--- from the data structure using 'genSource'. This will be stored in 'Text' and
--- can then be processed further.
-class Source a where
- genSource :: a -> Text
-
-positiveArb :: (QC.Arbitrary a, Ord a, Num a) => QC.Gen a
-positiveArb = QC.suchThat QC.arbitrary (>0)
-
-instance QC.Arbitrary Text where
- arbitrary = T.pack <$> QC.arbitrary
-
--- | Identifier in Verilog. This is just a string of characters that can either
--- be lowercase and uppercase for now. This might change in the future though,
--- as Verilog supports many more characters in Identifiers.
-newtype Identifier = Identifier { _getIdentifier :: Text }
- deriving (Eq, IsString, Semigroup, Monoid)
-
-makeLenses ''Identifier
-
-instance Show Identifier where
- show i = T.unpack $ i ^. getIdentifier
-
-instance QC.Arbitrary Identifier where
- arbitrary = do
- l <- QC.choose (2, 10)
- Identifier . T.pack <$> replicateM l (QC.elements ['a'..'z'])
-
--- | Verilog syntax for adding a delay, which is represented as @#num@.
-newtype Delay = Delay { _delay :: Int }
- deriving (Eq)
-
-instance Num Delay where
- Delay a + Delay b = Delay $ a + b
- Delay a - Delay b = Delay $ a - b
- Delay a * Delay b = Delay $ a * b
- negate (Delay a) = Delay $ negate a
- abs (Delay a) = Delay $ abs a
- signum (Delay a) = Delay $ signum a
- fromInteger = Delay . fromInteger
-
-instance QC.Arbitrary Delay where
- arbitrary = Delay <$> positiveArb
-
--- | Verilog syntax for an event, such as @\@x@, which is used for always blocks
-data Event = EId Identifier
- | EExpr Expr
- | EAll
- deriving (Eq)
-
-instance QC.Arbitrary Event where
- arbitrary = EId <$> QC.arbitrary
-
--- | Binary operators that are currently supported in the verilog generation.
-data BinaryOperator = BinPlus -- ^ @+@
- | BinMinus -- ^ @-@
- | BinTimes -- ^ @*@
- | BinDiv -- ^ @/@
- | BinMod -- ^ @%@
- | BinEq -- ^ @==@
- | BinNEq -- ^ @!=@
- | BinCEq -- ^ @===@
- | BinCNEq -- ^ @!==@
- | BinLAnd -- ^ @&&@
- | BinLOr -- ^ @||@
- | BinLT -- ^ @<@
- | BinLEq -- ^ @<=@
- | BinGT -- ^ @>@
- | BinGEq -- ^ @>=@
- | BinAnd -- ^ @&@
- | BinOr -- ^ @|@
- | BinXor -- ^ @^@
- | BinXNor -- ^ @^~@
- | BinXNorInv -- ^ @~^@
- | BinPower -- ^ @**@
- | BinLSL -- ^ @<<@
- | BinLSR -- ^ @>>@
- | BinASL -- ^ @<<<@
- | BinASR -- ^ @>>>@
- deriving (Eq)
-
-instance QC.Arbitrary BinaryOperator where
- arbitrary = QC.elements
- [ BinPlus
- , BinMinus
- , BinTimes
- , BinDiv
- , BinMod
- , BinEq
- , BinNEq
- , BinCEq
- , BinCNEq
- , BinLAnd
- , BinLOr
- , BinLT
- , BinLEq
- , BinGT
- , BinGEq
- , BinAnd
- , BinOr
- , BinXor
- , BinXNor
- , BinXNorInv
- , BinPower
- , BinLSL
- , BinLSR
- , BinASL
- , BinASR
- ]
-
--- | Unary operators that are currently supported by the generator.
-data UnaryOperator = UnPlus -- ^ @+@
- | UnMinus -- ^ @-@
- | UnNot -- ^ @!@
- | UnAnd -- ^ @&@
- | UnNand -- ^ @~&@
- | UnOr -- ^ @|@
- | UnNor -- ^ @~|@
- | UnXor -- ^ @^@
- | UnNxor -- ^ @~^@
- | UnNxorInv -- ^ @^~@
- deriving (Eq)
-
-instance QC.Arbitrary UnaryOperator where
- arbitrary = QC.elements
- [ UnPlus
- , UnMinus
- , UnNot
- , UnAnd
- , UnNand
- , UnOr
- , UnNor
- , UnXor
- , UnNxor
- , UnNxorInv
- ]
-
--- | Verilog expression, which can either be a primary expression, unary
--- expression, binary operator expression or a conditional expression.
-data Expr = Number { _numSize :: Int
- , _numVal :: Integer
- }
- | Id { _exprId :: Identifier }
- | Concat { _concatExpr :: [Expr] }
- | UnOp { _exprUnOp :: UnaryOperator
- , _exprPrim :: Expr
- }
- | BinOp { _exprLhs :: Expr
- , _exprBinOp :: BinaryOperator
- , _exprRhs :: Expr
- }
- | Cond { _exprCond :: Expr
- , _exprTrue :: Expr
- , _exprFalse :: Expr
- }
- | Str { _exprStr :: Text }
- deriving (Eq)
-
-instance Num Expr where
- a + b = BinOp a BinPlus b
- a - b = BinOp a BinMinus b
- a * b = BinOp a BinTimes b
- negate = UnOp UnMinus
- abs = undefined
- signum = undefined
- fromInteger = Number 32 . fromInteger
-
-instance Semigroup Expr where
- (Concat a) <> (Concat b) = Concat $ a <> b
- (Concat a) <> b = Concat $ a <> [b]
- a <> (Concat b) = Concat $ a : b
- a <> b = Concat [a, b]
-
-instance Monoid Expr where
- mempty = Concat []
-
-instance IsString Expr where
- fromString = Str . fromString
-
-expr :: Int -> QC.Gen Expr
-expr 0 = QC.oneof
- [ Id <$> QC.arbitrary
- , Number <$> positiveArb <*> QC.arbitrary
- , UnOp <$> QC.arbitrary <*> QC.arbitrary
- -- , Str <$> QC.arbitrary
- ]
-expr n
- | n > 0 = QC.oneof
- [ Id <$> QC.arbitrary
- , Number <$> positiveArb <*> QC.arbitrary
- , Concat <$> QC.listOf1 (subexpr 4)
- , UnOp <$> QC.arbitrary <*> QC.arbitrary
- -- , Str <$> QC.arbitrary
- , BinOp <$> subexpr 2 <*> QC.arbitrary <*> subexpr 2
- , Cond <$> subexpr 3 <*> subexpr 3 <*> subexpr 3
- ]
- | otherwise = expr 0
- where
- subexpr y = expr (n `div` y)
-
-instance QC.Arbitrary Expr where
- arbitrary = QC.sized expr
-
-traverseExpr :: (Applicative f) => (Expr -> f Expr) -> Expr -> f Expr
-traverseExpr f (Concat e) = Concat <$> sequenceA (f <$> e)
-traverseExpr f (UnOp un e) = UnOp un <$> f e
-traverseExpr f (BinOp l op r) = BinOp <$> f l <*> pure op <*> f r
-traverseExpr f (Cond c l r) = Cond <$> f c <*> f l <*> f r
-traverseExpr _ e = pure e
-
-makeLenses ''Expr
-
--- | Constant expression, which are known before simulation at compilation time.
-newtype ConstExpr = ConstExpr { _constNum :: Int }
- deriving (Eq, Num)
-
-instance QC.Arbitrary ConstExpr where
- arbitrary = ConstExpr <$> positiveArb
-
--- | Type that represents the left hand side of an assignment, which can be a
--- concatenation such as in:
---
--- @
--- {a, b, c} = 32'h94238;
--- @
-data LVal = RegId Identifier
- | RegExpr { _regExprId :: Identifier
- , _regExpr :: Expr
- }
- | RegSize { _regSizeId :: Identifier
- , _regSizeMSB :: ConstExpr
- , _regSizeLSB :: ConstExpr
- }
- | RegConcat { _regConc :: [Expr] }
- deriving (Eq)
-
-makeLenses ''LVal
-
-instance QC.Arbitrary LVal where
- arbitrary = QC.oneof [ RegId <$> QC.arbitrary
- , RegExpr <$> QC.arbitrary <*> QC.arbitrary
- , RegSize <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
- ]
-
--- | Different port direction that are supported in Verilog.
-data PortDir = PortIn -- ^ Input direction for port (@input@).
- | PortOut -- ^ Output direction for port (@output@).
- | PortInOut -- ^ Inout direction for port (@inout@).
- deriving (Eq)
-
-instance QC.Arbitrary PortDir where
- arbitrary = QC.elements [PortIn, PortOut, PortInOut]
-
--- | Currently, only @wire@ and @reg@ are supported, as the other net types are
--- not that common and not a priority.
-data PortType = Wire
- | Reg { _regSigned :: Bool }
- deriving (Eq)
-
-instance QC.Arbitrary PortType where
- arbitrary = QC.oneof [pure Wire, Reg <$> QC.arbitrary]
-
-makeLenses ''PortType
-
--- | Port declaration. It contains information about the type of the port, the
--- size, and the port name. It used to also contain information about if it was
--- an input or output port. However, this is not always necessary and was more
--- cumbersome than useful, as a lot of ports can be declared without input and
--- output port.
---
--- This is now implemented inside 'ModDecl' itself, which uses a list of output
--- and input ports.
-data Port = Port { _portType :: PortType
- , _portSize :: Int
- , _portName :: Identifier
- } deriving (Eq)
-
-makeLenses ''Port
-
-instance QC.Arbitrary Port where
- arbitrary = Port <$> QC.arbitrary <*> positiveArb <*> QC.arbitrary
-
--- | This is currently a type because direct module declaration should also be
--- added:
---
--- @
--- mod a(.y(y1), .x1(x11), .x2(x22));
--- @
-newtype ModConn = ModConn { _modConn :: Expr }
- deriving (Eq)
-
-makeLenses ''ModConn
-
-instance QC.Arbitrary ModConn where
- arbitrary = ModConn <$> QC.arbitrary
-
-data Assign = Assign { _assignReg :: LVal
- , _assignDelay :: Maybe Delay
- , _assignExpr :: Expr
- } deriving (Eq)
-
-instance QC.Arbitrary Assign where
- arbitrary = Assign <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
-
-data ContAssign = ContAssign { _contAssignNetLVal :: Identifier
- , _contAssignExpr :: Expr
- } deriving (Eq)
-
-makeLenses ''ContAssign
-
-instance QC.Arbitrary ContAssign where
- arbitrary = ContAssign <$> QC.arbitrary <*> QC.arbitrary
-
--- | Stmnts in Verilog.
-data Stmnt = TimeCtrl { _statDelay :: Delay
- , _statDStat :: Maybe Stmnt
- } -- ^ Time control (@#NUM@)
- | EventCtrl { _statEvent :: Event
- , _statEStat :: Maybe Stmnt
- }
- | SeqBlock { _statements :: [Stmnt] } -- ^ Sequential block (@begin ... end@)
- | BlockAssign Assign -- ^ blocking assignment (@=@)
- | NonBlockAssign Assign -- ^ Non blocking assignment (@<=@)
- | StatCA ContAssign -- ^ Stmnt continuous assignment. May not be correct.
- | TaskEnable Task
- | SysTaskEnable Task
- deriving (Eq)
-
-instance Semigroup Stmnt where
- (SeqBlock a) <> (SeqBlock b) = SeqBlock $ a <> b
- (SeqBlock a) <> b = SeqBlock $ a <> [b]
- a <> (SeqBlock b) = SeqBlock $ a : b
- a <> b = SeqBlock [a, b]
-
-instance Monoid Stmnt where
- mempty = SeqBlock []
-
-statement :: Int -> QC.Gen Stmnt
-statement 0 = QC.oneof
- [ BlockAssign <$> QC.arbitrary
- , NonBlockAssign <$> QC.arbitrary
- -- , StatCA <$> QC.arbitrary
- , TaskEnable <$> QC.arbitrary
- , SysTaskEnable <$> QC.arbitrary
- ]
-statement n
- | n > 0 = QC.oneof
- [ TimeCtrl <$> QC.arbitrary <*> (Just <$> substat 2)
- , SeqBlock <$> QC.listOf1 (substat 4)
- , BlockAssign <$> QC.arbitrary
- , NonBlockAssign <$> QC.arbitrary
- -- , StatCA <$> QC.arbitrary
- , TaskEnable <$> QC.arbitrary
- , SysTaskEnable <$> QC.arbitrary
- ]
- | otherwise = statement 0
- where
- substat y = statement (n `div` y)
-
-instance QC.Arbitrary Stmnt where
- arbitrary = QC.sized statement
-
-data Task = Task { _taskName :: Identifier
- , _taskExpr :: [Expr]
- } deriving (Eq)
-
-makeLenses ''Task
-
-instance QC.Arbitrary Task where
- arbitrary = Task <$> QC.arbitrary <*> QC.arbitrary
-
--- | Module item which is the body of the module expression.
-data ModItem = ModCA ContAssign
- | ModInst { _modInstId :: Identifier
- , _modInstName :: Identifier
- , _modInstConns :: [ModConn]
- }
- | Initial Stmnt
- | Always Stmnt
- | Decl { declDir :: Maybe PortDir
- , declPort :: Port
- }
- deriving (Eq)
-
-makeLenses ''ModItem
-
-instance QC.Arbitrary ModItem where
- arbitrary = QC.oneof [ ModCA <$> QC.arbitrary
- , ModInst <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
- , Initial <$> QC.arbitrary
- , Always <$> (EventCtrl <$> QC.arbitrary <*> QC.arbitrary)
- , Decl <$> pure Nothing <*> QC.arbitrary
- ]
-
--- | 'module' module_identifier [list_of_ports] ';' { module_item } 'end_module'
-data ModDecl = ModDecl { _moduleId :: Identifier
- , _modOutPorts :: [Port]
- , _modInPorts :: [Port]
- , _moduleItems :: [ModItem]
- } deriving (Eq)
-
-makeLenses ''ModDecl
-
-modPortGen :: QC.Gen Port
-modPortGen = QC.oneof
- [ Port Wire <$> positiveArb <*> QC.arbitrary
- , Port <$> (Reg <$> QC.arbitrary) <*> positiveArb <*> QC.arbitrary
- ]
-
-
-instance QC.Arbitrary ModDecl where
- arbitrary = ModDecl <$> QC.arbitrary <*> QC.arbitrary
- <*> QC.listOf1 modPortGen <*> QC.arbitrary
-
--- | Description of the Verilog module.
-newtype Description = Description { _getDescription :: ModDecl }
- deriving (Eq)
-
-makeLenses ''Description
-
-instance QC.Arbitrary Description where
- arbitrary = Description <$> QC.arbitrary
-
--- | The complete sourcetext for the Verilog module.
-newtype VerilogSrc = VerilogSrc { _getVerilogSrc :: [Description] }
- deriving (Eq)
-
-makeLenses ''VerilogSrc
-
-instance Semigroup VerilogSrc where
- VerilogSrc a <> VerilogSrc b = VerilogSrc $ a ++ b
-
-instance Monoid VerilogSrc where
- mempty = VerilogSrc []
-
-instance QC.Arbitrary VerilogSrc where
- arbitrary = VerilogSrc <$> QC.arbitrary
diff --git a/src/Test/VeriFuzz/Verilog/Arbitrary.hs b/src/Test/VeriFuzz/Verilog/Arbitrary.hs
deleted file mode 100644
index 1bcb727..0000000
--- a/src/Test/VeriFuzz/Verilog/Arbitrary.hs
+++ /dev/null
@@ -1,184 +0,0 @@
-{-|
-Module : Test.VeriFuzz.Verilog.Arbitrary
-Description : Arbitrary instances for the AST.
-Copyright : (c) 2018-2019, Yann Herklotz Grave
-License : GPL-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Portability : POSIX
-
-Arbitrary instances for the AST.
--}
-
-module Test.VeriFuzz.Verilog.Arbitrary where
-
-import Control.Monad (replicateM)
-import Data.Text (Text)
-import qualified Data.Text as T
-import qualified Test.QuickCheck as QC
-import Test.VeriFuzz.Verilog.AST
-
--- Generate Arbitrary instances for the AST
-
-positiveArb :: (QC.Arbitrary a, Ord a, Num a) => QC.Gen a
-positiveArb = QC.suchThat QC.arbitrary (>0)
-
-expr :: Int -> QC.Gen Expr
-expr 0 = QC.oneof
- [ Id <$> QC.arbitrary
- , Number <$> positiveArb <*> QC.arbitrary
- , UnOp <$> QC.arbitrary <*> QC.arbitrary
- -- , Str <$> QC.arbitrary
- ]
-expr n
- | n > 0 = QC.oneof
- [ Id <$> QC.arbitrary
- , Number <$> positiveArb <*> QC.arbitrary
- , Concat <$> QC.listOf1 (subexpr 4)
- , UnOp <$> QC.arbitrary <*> QC.arbitrary
- -- , Str <$> QC.arbitrary
- , BinOp <$> subexpr 2 <*> QC.arbitrary <*> subexpr 2
- , Cond <$> subexpr 3 <*> subexpr 3 <*> subexpr 3
- ]
- | otherwise = expr 0
- where
- subexpr y = expr (n `div` y)
-
-statement :: Int -> QC.Gen Stmnt
-statement 0 = QC.oneof
- [ BlockAssign <$> QC.arbitrary
- , NonBlockAssign <$> QC.arbitrary
- -- , StatCA <$> QC.arbitrary
- , TaskEnable <$> QC.arbitrary
- , SysTaskEnable <$> QC.arbitrary
- ]
-statement n
- | n > 0 = QC.oneof
- [ TimeCtrl <$> QC.arbitrary <*> (Just <$> substat 2)
- , SeqBlock <$> QC.listOf1 (substat 4)
- , BlockAssign <$> QC.arbitrary
- , NonBlockAssign <$> QC.arbitrary
- -- , StatCA <$> QC.arbitrary
- , TaskEnable <$> QC.arbitrary
- , SysTaskEnable <$> QC.arbitrary
- ]
- | otherwise = statement 0
- where
- substat y = statement (n `div` y)
-
-modPortGen :: QC.Gen Port
-modPortGen = QC.oneof
- [ Port Wire <$> positiveArb <*> QC.arbitrary
- , Port <$> (Reg <$> QC.arbitrary) <*> positiveArb <*> QC.arbitrary
- ]
-
-instance QC.Arbitrary Text where
- arbitrary = T.pack <$> QC.arbitrary
-
-instance QC.Arbitrary Identifier where
- arbitrary = do
- l <- QC.choose (2, 10)
- Identifier . T.pack <$> replicateM l (QC.elements ['a'..'z'])
-
-instance QC.Arbitrary BinaryOperator where
- arbitrary = QC.elements
- [ BinPlus
- , BinMinus
- , BinTimes
- , BinDiv
- , BinMod
- , BinEq
- , BinNEq
- , BinCEq
- , BinCNEq
- , BinLAnd
- , BinLOr
- , BinLT
- , BinLEq
- , BinGT
- , BinGEq
- , BinAnd
- , BinOr
- , BinXor
- , BinXNor
- , BinXNorInv
- , BinPower
- , BinLSL
- , BinLSR
- , BinASL
- , BinASR
- ]
-
-instance QC.Arbitrary UnaryOperator where
- arbitrary = QC.elements
- [ UnPlus
- , UnMinus
- , UnNot
- , UnAnd
- , UnNand
- , UnOr
- , UnNor
- , UnXor
- , UnNxor
- , UnNxorInv
- ]
-
-instance QC.Arbitrary PortDir where
- arbitrary = QC.elements [PortIn, PortOut, PortInOut]
-
-instance QC.Arbitrary PortType where
- arbitrary = QC.oneof [pure Wire, Reg <$> QC.arbitrary]
-
-instance QC.Arbitrary Port where
- arbitrary = Port <$> QC.arbitrary <*> positiveArb <*> QC.arbitrary
-
-instance QC.Arbitrary Delay where
- arbitrary = Delay <$> positiveArb
-
-instance QC.Arbitrary Event where
- arbitrary = EId <$> QC.arbitrary
-
-instance QC.Arbitrary ModConn where
- arbitrary = ModConn <$> QC.arbitrary
-
-instance QC.Arbitrary ConstExpr where
- arbitrary = ConstExpr <$> positiveArb
-
-instance QC.Arbitrary LVal where
- arbitrary = QC.oneof [ RegId <$> QC.arbitrary
- , RegExpr <$> QC.arbitrary <*> QC.arbitrary
- , RegSize <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
- ]
-
-instance QC.Arbitrary Assign where
- arbitrary = Assign <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
-
-instance QC.Arbitrary Expr where
- arbitrary = QC.sized expr
-
-instance QC.Arbitrary Stmnt where
- arbitrary = QC.sized statement
-
-instance QC.Arbitrary ContAssign where
- arbitrary = ContAssign <$> QC.arbitrary <*> QC.arbitrary
-
-instance QC.Arbitrary Task where
- arbitrary = Task <$> QC.arbitrary <*> QC.arbitrary
-
-instance QC.Arbitrary ModItem where
- arbitrary = QC.oneof [ ModCA <$> QC.arbitrary
- , ModInst <$> QC.arbitrary <*> QC.arbitrary <*> QC.arbitrary
- , Initial <$> QC.arbitrary
- , Always <$> (EventCtrl <$> QC.arbitrary <*> QC.arbitrary)
- , Decl <$> pure Nothing <*> QC.arbitrary
- ]
-
-instance QC.Arbitrary ModDecl where
- arbitrary = ModDecl <$> QC.arbitrary <*> QC.arbitrary
- <*> QC.listOf1 modPortGen <*> QC.arbitrary
-
-instance QC.Arbitrary Description where
- arbitrary = Description <$> QC.arbitrary
-
-instance QC.Arbitrary VerilogSrc where
- arbitrary = VerilogSrc <$> QC.arbitrary
diff --git a/src/Test/VeriFuzz/Verilog/CodeGen.hs b/src/Test/VeriFuzz/Verilog/CodeGen.hs
deleted file mode 100644
index d97c8b9..0000000
--- a/src/Test/VeriFuzz/Verilog/CodeGen.hs
+++ /dev/null
@@ -1,315 +0,0 @@
-{-|
-Module : VeriFuzz.Verilog.CodeGen
-Description : Code generation for Verilog AST.
-Copyright : (c) 2018-2019, Yann Herklotz Grave
-License : BSD-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Portability : POSIX
-
-This module generates the code from the Verilog AST defined in
-"VeriFuzz.Verilog.AST".
--}
-
-module VeriFuzz.Verilog.CodeGen where
-
-import Control.Lens
-import Data.Foldable (fold)
-import Data.Maybe (isNothing)
-import Data.Text (Text)
-import qualified Data.Text as T
-import qualified Data.Text.IO as T
-import Numeric (showHex)
-import VeriFuzz.Internal.Shared
-import VeriFuzz.Verilog.AST
-
--- | Inserts commas between '[Text]' and except the last one.
-comma :: [Text] -> Text
-comma = T.intercalate ", "
-
--- | Show function for 'Text'
-showT :: (Show a) => a -> Text
-showT = T.pack . show
-
--- | Map a 'Maybe Stmnt' to 'Text'. If it is 'Just stmnt', the generated
--- statements are returned. If it is 'Nothing', then @;\n@ is returned.
-defMap :: Maybe Stmnt -> Text
-defMap = maybe ";\n" genStmnt
-
--- | Convert the 'VerilogSrc' type to 'Text' so that it can be rendered.
-genVerilogSrc :: VerilogSrc -> Text
-genVerilogSrc source =
- fold $ genDescription <$> source ^. getVerilogSrc
-
--- | Generate the 'Description' to 'Text'.
-genDescription :: Description -> Text
-genDescription desc =
- genModuleDecl $ desc ^. getDescription
-
--- | Generate the 'ModDecl' for a module and convert it to 'Text'.
-genModuleDecl :: ModDecl -> Text
-genModuleDecl mod =
- "module " <> mod ^. moduleId . getIdentifier
- <> ports <> ";\n"
- <> modItems
- <> "endmodule\n"
- where
- ports
- | noIn && noOut = ""
- | otherwise = "(" <> comma (genModPort <$> outIn) <> ")"
- modItems = fold $ genModuleItem <$> mod ^. moduleItems
- noOut = null $ mod ^. modOutPorts
- noIn = null $ mod ^. modInPorts
- outIn = (mod ^. modOutPorts) ++ (mod ^. modInPorts)
-
--- | Conversts 'Port' to 'Text' for the module list, which means it only
--- generates a list of identifiers.
-genModPort :: Port -> Text
-genModPort port = port ^. portName . getIdentifier
-
--- | Generate the 'Port' description.
-genPort :: Port -> Text
-genPort port =
- t <> size <> name
- where
- t = (<>" ") . genPortType $ port ^. portType
- size
- | port ^. portSize > 1 = "[" <> showT (port ^. portSize - 1) <> ":0] "
- | otherwise = ""
- name = port ^. portName . getIdentifier
-
--- | Convert the 'PortDir' type to 'Text'.
-genPortDir :: PortDir -> Text
-genPortDir PortIn = "input"
-genPortDir PortOut = "output"
-genPortDir PortInOut = "inout"
-
--- | Generate a 'ModItem'.
-genModuleItem :: ModItem -> Text
-genModuleItem (ModCA ca) = genContAssign ca
-genModuleItem (ModInst (Identifier id) (Identifier name) conn) =
- id <> " " <> name <> "(" <> comma (genExpr . _modConn <$> conn) <> ")" <> ";\n"
-genModuleItem (Initial stat) = "initial " <> genStmnt stat
-genModuleItem (Always stat) = "always " <> genStmnt stat
-genModuleItem (Decl dir port) =
- (maybe "" makePort dir) <> genPort port <> ";\n"
- where
- makePort = (<>" ") . genPortDir
-
--- | Generate continuous assignment
-genContAssign :: ContAssign -> Text
-genContAssign (ContAssign val e) =
- "assign " <> name <> " = " <> expr <> ";\n"
- where
- name = val ^. getIdentifier
- expr = genExpr e
-
--- | Generate 'Expr' to 'Text'.
-genExpr :: Expr -> Text
-genExpr (BinOp exprRhs bin exprLhs) =
- "(" <> genExpr exprRhs <> genBinaryOperator bin <> genExpr exprLhs <> ")"
-genExpr (Number s n) =
- showT s <> "'h" <> T.pack (showHex n "")
-genExpr (Id i) = i ^. getIdentifier
-genExpr (Concat c) = "{" <> comma (genExpr <$> c) <> "}"
-genExpr (UnOp u e) =
- "(" <> genUnaryOperator u <> genExpr e <> ")"
-genExpr (Cond l t f) =
- "(" <> genExpr l <> " ? " <> genExpr t <> " : " <> genExpr f <> ")"
-genExpr (Str t) = "\"" <> t <> "\""
-
--- | Convert 'BinaryOperator' to 'Text'.
-genBinaryOperator :: BinaryOperator -> Text
-genBinaryOperator BinPlus = " + "
-genBinaryOperator BinMinus = " - "
-genBinaryOperator BinTimes = " * "
-genBinaryOperator BinDiv = " / "
-genBinaryOperator BinMod = " % "
-genBinaryOperator BinEq = " == "
-genBinaryOperator BinNEq = " != "
-genBinaryOperator BinCEq = " === "
-genBinaryOperator BinCNEq = " !== "
-genBinaryOperator BinLAnd = " && "
-genBinaryOperator BinLOr = " || "
-genBinaryOperator BinLT = " < "
-genBinaryOperator BinLEq = " <= "
-genBinaryOperator BinGT = " > "
-genBinaryOperator BinGEq = " >= "
-genBinaryOperator BinAnd = " & "
-genBinaryOperator BinOr = " | "
-genBinaryOperator BinXor = " ^ "
-genBinaryOperator BinXNor = " ^~ "
-genBinaryOperator BinXNorInv = " ~^ "
-genBinaryOperator BinPower = " ** "
-genBinaryOperator BinLSL = " << "
-genBinaryOperator BinLSR = " >> "
-genBinaryOperator BinASL = " <<< "
-genBinaryOperator BinASR = " >>> "
-
--- | Convert 'UnaryOperator' to 'Text'.
-genUnaryOperator :: UnaryOperator -> Text
-genUnaryOperator UnPlus = "+"
-genUnaryOperator UnMinus = "-"
-genUnaryOperator UnNot = "!"
-genUnaryOperator UnAnd = "&"
-genUnaryOperator UnNand = "~&"
-genUnaryOperator UnOr = "|"
-genUnaryOperator UnNor = "~|"
-genUnaryOperator UnXor = "^"
-genUnaryOperator UnNxor = "~^"
-genUnaryOperator UnNxorInv = "^~"
-
--- | Generate verilog code for an 'Event'.
-genEvent :: Event -> Text
-genEvent (EId id) = "@(" <> id ^. getIdentifier <> ")"
-genEvent (EExpr expr) = "@(" <> genExpr expr <> ")"
-genEvent EAll = "@*"
-
--- | Generates verilog code for a 'Delay'.
-genDelay :: Delay -> Text
-genDelay (Delay i) = "#" <> showT i
-
--- | Generate the verilog code for an 'LVal'.
-genLVal :: LVal -> Text
-genLVal (RegId id) = id ^. getIdentifier
-genLVal (RegExpr id expr) =
- id ^. getIdentifier <> " [" <> genExpr expr <> "]"
-genLVal (RegSize id msb lsb) =
- id ^. getIdentifier <> " [" <> genConstExpr msb <> ":" <> genConstExpr lsb <> "]"
-genLVal (RegConcat e) =
- "{" <> comma (genExpr <$> e) <> "}"
-
-genConstExpr :: ConstExpr -> Text
-genConstExpr (ConstExpr num) = showT num
-
-genPortType :: PortType -> Text
-genPortType Wire = "wire"
-genPortType (Reg signed)
- | signed = "reg signed"
- | otherwise = "reg"
-
-genAssign :: Text -> Assign -> Text
-genAssign op (Assign r d e) =
- genLVal r <> op <> maybe "" genDelay d <> genExpr e
-
-genStmnt :: Stmnt -> Text
-genStmnt (TimeCtrl d stat) = genDelay d <> " " <> defMap stat
-genStmnt (EventCtrl e stat) = genEvent e <> " " <> defMap stat
-genStmnt (SeqBlock s) =
- "begin\n" <> fold (genStmnt <$> s) <> "end\n"
-genStmnt (BlockAssign a) = genAssign " = " a <> ";\n"
-genStmnt (NonBlockAssign a) = genAssign " <= " a <> ";\n"
-genStmnt (StatCA a) = genContAssign a
-genStmnt (TaskEnable task) = genTask task <> ";\n"
-genStmnt (SysTaskEnable task) = "$" <> genTask task <> ";\n"
-
-genTask :: Task -> Text
-genTask (Task name expr)
- | null expr = id
- | otherwise = id <> "(" <> comma (genExpr <$> expr) <> ")"
- where
- id = name ^. getIdentifier
-
--- | Render the 'Text' to 'IO'. This is equivalent to 'putStrLn'.
-render :: Text -> IO ()
-render = T.putStrLn
-
--- Instances
-
-instance Source Task where
- genSource = genTask
-
-instance Source Stmnt where
- genSource = genStmnt
-
-instance Source PortType where
- genSource = genPortType
-
-instance Source ConstExpr where
- genSource = genConstExpr
-
-instance Source LVal where
- genSource = genLVal
-
-instance Source Delay where
- genSource = genDelay
-
-instance Source Event where
- genSource = genEvent
-
-instance Source UnaryOperator where
- genSource = genUnaryOperator
-
-instance Source Expr where
- genSource = genExpr
-
-instance Source ContAssign where
- genSource = genContAssign
-
-instance Source ModItem where
- genSource = genModuleItem
-
-instance Source PortDir where
- genSource = genPortDir
-
-instance Source Port where
- genSource = genPort
-
-instance Source ModDecl where
- genSource = genModuleDecl
-
-instance Source Description where
- genSource = genDescription
-
-instance Source VerilogSrc where
- genSource = genVerilogSrc
-
--- Show instances
-
-instance Show Task where
- show = T.unpack . genTask
-
-instance Show Stmnt where
- show = T.unpack . genStmnt
-
-instance Show PortType where
- show = T.unpack . genPortType
-
-instance Show ConstExpr where
- show = T.unpack . genConstExpr
-
-instance Show LVal where
- show = T.unpack . genLVal
-
-instance Show Delay where
- show = T.unpack . genDelay
-
-instance Show Event where
- show = T.unpack . genEvent
-
-instance Show UnaryOperator where
- show = T.unpack . genUnaryOperator
-
-instance Show Expr where
- show = T.unpack . genExpr
-
-instance Show ContAssign where
- show = T.unpack . genContAssign
-
-instance Show ModItem where
- show = T.unpack . genModuleItem
-
-instance Show PortDir where
- show = T.unpack . genPortDir
-
-instance Show Port where
- show = T.unpack . genPort
-
-instance Show ModDecl where
- show = T.unpack . genModuleDecl
-
-instance Show Description where
- show = T.unpack . genDescription
-
-instance Show VerilogSrc where
- show = T.unpack . genVerilogSrc
diff --git a/src/Test/VeriFuzz/Verilog/Helpers.hs b/src/Test/VeriFuzz/Verilog/Helpers.hs
deleted file mode 100644
index 0204379..0000000
--- a/src/Test/VeriFuzz/Verilog/Helpers.hs
+++ /dev/null
@@ -1,75 +0,0 @@
-{-|
-Module : VeriFuzz.Verilog.Helpers
-Description : Defaults and common functions.
-Copyright : (c) 2018-2019, Yann Herklotz Grave
-License : BSD-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Portability : POSIX
-
-Defaults and common functions.
--}
-
-module VeriFuzz.Verilog.Helpers where
-
-import Control.Lens
-import Data.Text (Text)
-import qualified Data.Text
-import VeriFuzz.Verilog.AST
-
-regDecl :: Identifier -> ModItem
-regDecl = Decl Nothing . Port (Reg False) 1
-
-wireDecl :: Identifier -> ModItem
-wireDecl = Decl Nothing . Port Wire 1
-
-modConn :: Identifier -> ModConn
-modConn = ModConn . Id
-
--- | Create an empty module.
-emptyMod :: ModDecl
-emptyMod = ModDecl "" [] [] []
-
--- | Set a module name for a module declaration.
-setModName :: Text -> ModDecl -> ModDecl
-setModName str = moduleId .~ Identifier str
-
--- | Add a input port to the module declaration.
-addModPort :: Port -> ModDecl -> ModDecl
-addModPort port = modInPorts %~ (:) port
-
-addDescription :: Description -> VerilogSrc -> VerilogSrc
-addDescription desc = getVerilogSrc %~ (:) desc
-
-testBench :: ModDecl
-testBench =
- ModDecl "main" [] []
- [ regDecl "a"
- , regDecl "b"
- , wireDecl "c"
- , ModInst "and" "and_gate"
- [ modConn "c"
- , modConn "a"
- , modConn "b"
- ]
- , Initial $ SeqBlock
- [ BlockAssign . Assign (RegId "a") Nothing $ Number 1 1
- , BlockAssign . Assign (RegId "b") Nothing $ Number 1 1
- -- , TimeCtrl (Delay 1) . Just . SysTaskEnable $ Task "display"
- -- [ Str "%d & %d = %d"
- -- , PrimExpr $ PrimId "a"
- -- , PrimExpr $ PrimId "b"
- -- , PrimExpr $ PrimId "c"
- -- ]
- -- , SysTaskEnable $ Task "finish" []
- ]
- ]
-
-addTestBench :: VerilogSrc -> VerilogSrc
-addTestBench = addDescription $ Description testBench
-
-defaultPort :: Identifier -> Port
-defaultPort = Port Wire 1
-
-portToExpr :: Port -> Expr
-portToExpr (Port _ _ id) = Id id
diff --git a/src/Test/VeriFuzz/Verilog/Mutate.hs b/src/Test/VeriFuzz/Verilog/Mutate.hs
deleted file mode 100644
index 501d217..0000000
--- a/src/Test/VeriFuzz/Verilog/Mutate.hs
+++ /dev/null
@@ -1,148 +0,0 @@
-{-|
-Module : VeriFuzz.Verilog.Mutation
-Description : Functions to mutate the Verilog AST.
-Copyright : (c) 2018-2019, Yann Herklotz Grave
-License : BSD-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Portability : POSIX
-
-Functions to mutate the Verilog AST from "VeriFuzz.Verilog.AST" to generate
-more random patterns, such as nesting wires instead of creating new ones.
--}
-
-module VeriFuzz.Verilog.Mutate where
-
-import Control.Lens
-import Data.Maybe (catMaybes, fromMaybe)
-import VeriFuzz.Internal.Gen
-import VeriFuzz.Internal.Shared
-import VeriFuzz.Verilog.AST
-import VeriFuzz.Verilog.CodeGen
-
--- | Return if the 'Identifier' is in a 'ModDecl'.
-inPort :: Identifier -> ModDecl -> Bool
-inPort id mod = inInput
- where
- inInput = any (\a -> a ^. portName == id) $ mod ^. modInPorts ++ mod ^. modOutPorts
-
--- | Find the last assignment of a specific wire/reg to an expression, and
--- returns that expression.
-findAssign :: Identifier -> [ModItem] -> Maybe Expr
-findAssign id items =
- safe last . catMaybes $ isAssign <$> items
- where
- isAssign (ModCA (ContAssign val expr))
- | val == id = Just expr
- | otherwise = Nothing
- isAssign _ = Nothing
-
--- | Transforms an expression by replacing an Identifier with an
--- expression. This is used inside 'transformOf' and 'traverseExpr' to replace
--- the 'Identifier' recursively.
-idTrans :: Identifier -> Expr -> Expr -> Expr
-idTrans i expr (Id id)
- | id == i = expr
- | otherwise = Id id
-idTrans _ _ e = e
-
--- | Replaces the identifier recursively in an expression.
-replace :: Identifier -> Expr -> Expr -> Expr
-replace = (transformOf traverseExpr .) . idTrans
-
--- | Nest expressions for a specific 'Identifier'. If the 'Identifier' is not found,
--- the AST is not changed.
---
--- This could be improved by instead of only using the last assignment to the
--- wire that one finds, to use the assignment to the wire before the current
--- expression. This would require a different approach though.
-nestId :: Identifier -> ModDecl -> ModDecl
-nestId id mod
- | not $ inPort id mod =
- let expr = fromMaybe def . findAssign id $ mod ^. moduleItems
- in mod & get %~ replace id expr
- | otherwise = mod
- where
- get = moduleItems . traverse . _ModCA . contAssignExpr
- def = Id id
-
--- | Replaces an identifier by a expression in all the module declaration.
-nestSource :: Identifier -> VerilogSrc -> VerilogSrc
-nestSource id src =
- src & getVerilogSrc . traverse . getDescription %~ nestId id
-
--- | Nest variables in the format @w[0-9]*@ up to a certain number.
-nestUpTo :: Int -> VerilogSrc -> VerilogSrc
-nestUpTo i src =
- foldl (flip nestSource) src $ Identifier . fromNode <$> [1..i]
-
-allVars :: ModDecl -> [Identifier]
-allVars mod =
- (mod ^.. modOutPorts . traverse . portName) ++ (mod ^.. modInPorts . traverse . portName)
--- $setup
--- >>> let mod = (ModDecl (Identifier "m") [Port Wire 5 (Identifier "y")] [Port Wire 5 "x"] [])
--- >>> let main = (ModDecl "main" [] [] [])
-
--- | Add a Module Instantiation using 'ModInst' from the first module passed to
--- it to the body of the second module. It first has to make all the inputs into
--- @reg@.
---
--- >>> instantiateMod mod main
--- module main;
--- wire [4:0] y;
--- reg [4:0] x;
--- m m1(y, x);
--- endmodule
--- <BLANKLINE>
-instantiateMod :: ModDecl -> ModDecl -> ModDecl
-instantiateMod mod main =
- main & moduleItems %~ ((out ++ regIn ++ [inst])++)
- where
- out = Decl Nothing <$> mod ^. modOutPorts
- regIn = Decl Nothing <$> (mod ^. modInPorts & traverse . portType .~ Reg False)
- inst = ModInst (mod ^. moduleId) (mod ^. moduleId <> (Identifier . showT $ count+1)) conns
- count = length . filter (==mod ^. moduleId) $ main ^.. moduleItems . traverse . modInstId
- conns = ModConn . Id <$> allVars mod
-
--- | Instantiate without adding wire declarations. It also does not count the
--- current instantiations of the same module.
---
--- >>> instantiateMod_ mod main
--- m m(y, x);
--- <BLANKLINE>
-instantiateMod_ :: ModDecl -> ModItem
-instantiateMod_ mod =
- ModInst (mod ^. moduleId) (mod ^. moduleId) conns
- where
- conns = ModConn . Id <$>
- (mod ^.. modOutPorts . traverse . portName) ++ (mod ^.. modInPorts . traverse . portName)
-
--- | Initialise all the inputs and outputs to a module.
---
--- >>> initMod mod
--- module m(y, x);
--- output wire [4:0] y;
--- input wire [4:0] x;
--- endmodule
--- <BLANKLINE>
-initMod :: ModDecl -> ModDecl
-initMod mod = mod & moduleItems %~ ((out ++ inp)++)
- where
- out = Decl (Just PortOut) <$> (mod ^. modOutPorts)
- inp = Decl (Just PortIn) <$> (mod ^. modInPorts)
-
-makeIdFrom :: (Show a) => a -> Identifier -> Identifier
-makeIdFrom a i =
- (i<>) . Identifier . ("_"<>) $ showT a
-
--- | Make top level module for equivalence verification. Also takes in how many
--- modules to instantiate.
-makeTop :: Int -> ModDecl -> ModDecl
-makeTop i m =
- ModDecl (m ^. moduleId) ys (m ^. modInPorts) modItems
- where
- ys = Port Wire 90 . (flip makeIdFrom) "y" <$> [1..i]
- modItems = instantiateMod_ . modN <$> [1..i]
- modN n = m
- & moduleId %~ makeIdFrom n
- & modOutPorts .~ [Port Wire 90 (makeIdFrom n "y")]