aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorYann Herklotz <git@ymhg.org>2019-04-09 12:38:15 +0100
committerYann Herklotz <git@ymhg.org>2019-04-09 12:38:15 +0100
commitd350cd339797c6dd9056afa2b1dad5aed4c31cb9 (patch)
tree868474f18dfedc05d347cf16d09b5e770bc33293 /src
parent7653f8fd33162b8b166a12e125c988663ec2fe79 (diff)
downloadverismith-d350cd339797c6dd9056afa2b1dad5aed4c31cb9.tar.gz
verismith-d350cd339797c6dd9056afa2b1dad5aed4c31cb9.zip
Add Parameter type and remove Description
Diffstat (limited to 'src')
-rw-r--r--src/VeriFuzz.hs2
-rw-r--r--src/VeriFuzz/Circuit.hs1
-rw-r--r--src/VeriFuzz/Circuit/Gen.hs4
-rw-r--r--src/VeriFuzz/Internal.hs5
-rw-r--r--src/VeriFuzz/Sim/Icarus.hs4
-rw-r--r--src/VeriFuzz/Sim/Internal.hs4
-rw-r--r--src/VeriFuzz/Verilog.hs4
-rw-r--r--src/VeriFuzz/Verilog/AST.hs125
-rw-r--r--src/VeriFuzz/Verilog/Arbitrary.hs32
-rw-r--r--src/VeriFuzz/Verilog/CodeGen.hs79
-rw-r--r--src/VeriFuzz/Verilog/Gen.hs6
-rw-r--r--src/VeriFuzz/Verilog/Internal.hs12
-rw-r--r--src/VeriFuzz/Verilog/Mutate.hs8
-rw-r--r--src/VeriFuzz/Verilog/Parser.hs6
-rw-r--r--src/VeriFuzz/Verilog/Preprocess.hs7
15 files changed, 204 insertions, 95 deletions
diff --git a/src/VeriFuzz.hs b/src/VeriFuzz.hs
index ebedb0d..e46751a 100644
--- a/src/VeriFuzz.hs
+++ b/src/VeriFuzz.hs
@@ -56,7 +56,7 @@ generateByteString n = do
makeSrcInfo :: ModDecl -> SourceInfo
makeSrcInfo m =
- SourceInfo (m ^. modId . getIdentifier) (Verilog [Description m])
+ SourceInfo (m ^. modId . getIdentifier) (Verilog [m])
-- | Draw a randomly generated DAG to a dot file and compile it to a png so it
-- can be seen.
diff --git a/src/VeriFuzz/Circuit.hs b/src/VeriFuzz/Circuit.hs
index 37e25ac..d385d32 100644
--- a/src/VeriFuzz/Circuit.hs
+++ b/src/VeriFuzz/Circuit.hs
@@ -43,4 +43,3 @@ fromGraph = do
$ nestUpTo 5 (generateAST gr)
^.. getVerilog
. traverse
- . getDescription
diff --git a/src/VeriFuzz/Circuit/Gen.hs b/src/VeriFuzz/Circuit/Gen.hs
index 817d2f8..0b13ece 100644
--- a/src/VeriFuzz/Circuit/Gen.hs
+++ b/src/VeriFuzz/Circuit/Gen.hs
@@ -67,7 +67,7 @@ genAssignAST c = catMaybes $ genContAssignAST c <$> nodes
nodes = G.labNodes gr
genModuleDeclAST :: Circuit -> ModDecl
-genModuleDeclAST c = ModDecl i output ports $ combineAssigns yPort a
+genModuleDeclAST c = ModDecl i output ports (combineAssigns yPort a) []
where
i = Identifier "gen_module"
ports = genPortsAST inputsC c
@@ -76,4 +76,4 @@ genModuleDeclAST c = ModDecl i output ports $ combineAssigns yPort a
yPort = Port Wire False 90 "y"
generateAST :: Circuit -> Verilog
-generateAST c = Verilog [Description $ genModuleDeclAST c]
+generateAST c = Verilog [genModuleDeclAST c]
diff --git a/src/VeriFuzz/Internal.hs b/src/VeriFuzz/Internal.hs
index 51bb52c..22efa92 100644
--- a/src/VeriFuzz/Internal.hs
+++ b/src/VeriFuzz/Internal.hs
@@ -15,6 +15,7 @@ module VeriFuzz.Internal
safe
, showT
, comma
+ , commaNL
)
where
@@ -33,3 +34,7 @@ showT = T.pack . show
-- | Inserts commas between '[Text]' and except the last one.
comma :: [Text] -> Text
comma = T.intercalate ", "
+
+-- | Inserts commas and newlines between '[Text]' and except the last one.
+commaNL :: [Text] -> Text
+commaNL = T.intercalate ",\n"
diff --git a/src/VeriFuzz/Sim/Icarus.hs b/src/VeriFuzz/Sim/Icarus.hs
index 14023b7..9b5138f 100644
--- a/src/VeriFuzz/Sim/Icarus.hs
+++ b/src/VeriFuzz/Sim/Icarus.hs
@@ -92,9 +92,9 @@ runSimIcarus sim rinfo bss = do
[ Initial
$ fold (addDisplay $ assignFunc (_modInPorts m) <$> bss)
<> (SysTaskEnable $ Task "finish" [])
- ]
+ ] []
let newtb = instantiateMod m tb
- let modWithTb = Verilog $ Description <$> [newtb, m]
+ let modWithTb = Verilog [newtb, m]
writefile "main.v" $ genSource modWithTb
runSimWithFile sim "main.v" bss
where m = rinfo ^. mainModule
diff --git a/src/VeriFuzz/Sim/Internal.hs b/src/VeriFuzz/Sim/Internal.hs
index 062035c..925b155 100644
--- a/src/VeriFuzz/Sim/Internal.hs
+++ b/src/VeriFuzz/Sim/Internal.hs
@@ -73,10 +73,10 @@ mainModule = lens get_ set_
where
set_ (SourceInfo top main) v =
SourceInfo top (main & getModule %~ update top v)
- update top v m@(ModDecl (Identifier i) _ _ _) | i == top = v
+ update top v m@(ModDecl (Identifier i) _ _ _ _) | i == top = v
| otherwise = m
get_ (SourceInfo top main) = head . filter (f top) $ main ^.. getModule
- f top (ModDecl (Identifier i) _ _ _) = i == top
+ f top (ModDecl (Identifier i) _ _ _ _) = i == top
rootPath :: Sh FilePath
rootPath = do
diff --git a/src/VeriFuzz/Verilog.hs b/src/VeriFuzz/Verilog.hs
index e6f8c54..a45922b 100644
--- a/src/VeriFuzz/Verilog.hs
+++ b/src/VeriFuzz/Verilog.hs
@@ -18,8 +18,6 @@ module VeriFuzz.Verilog
, GenVerilog(..)
, genSource
, getVerilog
- , Description(..)
- , getDescription
-- * Primitives
-- ** Identifier
, Identifier(..)
@@ -69,7 +67,6 @@ module VeriFuzz.Verilog
, exprFunc
, exprBody
, exprStr
- , traverseExpr
, ConstExpr(..)
, constNum
, Function(..)
@@ -90,7 +87,6 @@ module VeriFuzz.Verilog
, statements
, stmntBA
, stmntNBA
- , stmntCA
, stmntTask
, stmntSysTask
, stmntCondExpr
diff --git a/src/VeriFuzz/Verilog/AST.hs b/src/VeriFuzz/Verilog/AST.hs
index 4473b96..f84eddf 100644
--- a/src/VeriFuzz/Verilog/AST.hs
+++ b/src/VeriFuzz/Verilog/AST.hs
@@ -18,8 +18,6 @@ module VeriFuzz.Verilog.AST
( -- * Top level types
Verilog(..)
, getVerilog
- , Description(..)
- , getDescription
-- * Primitives
-- ** Identifier
, Identifier(..)
@@ -69,9 +67,20 @@ module VeriFuzz.Verilog.AST
, exprFunc
, exprBody
, exprStr
- , traverseExpr
, ConstExpr(..)
+ , constSize
, constNum
+ , constParamId
+ , constConcat
+ , constUnOp
+ , constPrim
+ , constLhs
+ , constBinOp
+ , constRhs
+ , constCond
+ , constTrue
+ , constFalse
+ , constStr
, Function(..)
-- * Assignment
, Assign(..)
@@ -81,6 +90,13 @@ module VeriFuzz.Verilog.AST
, ContAssign(..)
, contAssignNetLVal
, contAssignExpr
+ -- ** Parameters
+ , Parameter(..)
+ , paramIdent
+ , paramValue
+ , LocalParam(..)
+ , localParamIdent
+ , localParamValue
-- * Statment
, Statement(..)
, statDelay
@@ -90,23 +106,29 @@ module VeriFuzz.Verilog.AST
, statements
, stmntBA
, stmntNBA
- , stmntCA
, stmntTask
, stmntSysTask
, stmntCondExpr
, stmntCondTrue
, stmntCondFalse
+ , forAssign
+ , forExpr
+ , forIncr
+ , forStmnt
-- * Module
, ModDecl(..)
, modId
, modOutPorts
, modInPorts
, modItems
+ , modParams
, ModItem(..)
, modContAssign
, modInstId
, modInstName
, modInstConns
+ , paramDecl
+ , localParamDecl
, traverseModItem
, declDir
, declPort
@@ -123,9 +145,10 @@ where
import Control.Lens
import Data.Data
import Data.Data.Lens
-import Data.String (IsString, fromString)
-import Data.Text (Text)
-import Data.Traversable (sequenceA)
+import Data.List.NonEmpty (NonEmpty)
+import Data.String (IsString, fromString)
+import Data.Text (Text)
+import Data.Traversable (sequenceA)
-- | 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,
@@ -239,17 +262,49 @@ instance IsString Expr where
instance Plated Expr where
plate = uniplate
-traverseExpr :: (Applicative f) => (Expr -> f Expr) -> Expr -> f Expr
-traverseExpr f (Concat e ) = Concat <$> sequenceA (f <$> e)
-traverseExpr f (UnOp u e ) = UnOp u <$> f e
-traverseExpr f (BinOp l o r) = BinOp <$> f l <*> pure o <*> f r
-traverseExpr f (Cond c l r) = Cond <$> f c <*> f l <*> f r
-traverseExpr f (Func fn e ) = Func fn <$> f e
-traverseExpr _ e = pure e
+-- | Constant expression, which are known before simulation at compile time.
+data ConstExpr = ConstNum { _constSize :: Int
+ , _constNum :: Integer
+ }
+ | ParamId { _constParamId :: {-# UNPACK #-} !Identifier }
+ | ConstConcat { _constConcat :: [ConstExpr] }
+ | ConstUnOp { _constUnOp :: !UnaryOperator
+ , _constPrim :: ConstExpr
+ }
+ | ConstBinOp { _constLhs :: ConstExpr
+ , _constBinOp :: !BinaryOperator
+ , _constRhs :: ConstExpr
+ }
+ | ConstCond { _constCond :: ConstExpr
+ , _constTrue :: ConstExpr
+ , _constFalse :: ConstExpr
+ }
+ | ConstStr { _constStr :: {-# UNPACK #-} !Text }
+ deriving (Eq, Show, Ord, Data)
+
+instance Num ConstExpr where
+ a + b = ConstBinOp a BinPlus b
+ a - b = ConstBinOp a BinMinus b
+ a * b = ConstBinOp a BinTimes b
+ negate = ConstUnOp UnMinus
+ abs = undefined
+ signum = undefined
+ fromInteger = ConstNum 32 . fromInteger
+
+instance Semigroup ConstExpr where
+ (ConstConcat a) <> (ConstConcat b) = ConstConcat $ a <> b
+ (ConstConcat a) <> b = ConstConcat $ a <> [b]
+ a <> (ConstConcat b) = ConstConcat $ a : b
+ a <> b = ConstConcat [a, b]
--- | Constant expression, which are known before simulation at compilation time.
-newtype ConstExpr = ConstExpr { _constNum :: Int }
- deriving (Eq, Show, Ord, Data, Num)
+instance Monoid ConstExpr where
+ mempty = ConstConcat []
+
+instance IsString ConstExpr where
+ fromString = ConstStr . fromString
+
+instance Plated ConstExpr where
+ plate = uniplate
data Task = Task { _taskName :: {-# UNPACK #-} !Identifier
, _taskExpr :: [Expr]
@@ -332,13 +387,17 @@ data Statement = TimeCtrl { _statDelay :: {-# UNPACK #-} !Delay
| SeqBlock { _statements :: [Statement] } -- ^ Sequential block (@begin ... end@)
| BlockAssign { _stmntBA :: !Assign } -- ^ blocking assignment (@=@)
| NonBlockAssign { _stmntNBA :: !Assign } -- ^ Non blocking assignment (@<=@)
- | StatCA { _stmntCA :: !ContAssign } -- ^ Statement continuous assignment. May not be correct.
| TaskEnable { _stmntTask :: !Task }
| SysTaskEnable { _stmntSysTask :: !Task }
| CondStmnt { _stmntCondExpr :: Expr
, _stmntCondTrue :: Maybe Statement
, _stmntCondFalse :: Maybe Statement
}
+ | ForLoop { _forAssign :: !Assign
+ , _forExpr :: Expr
+ , _forIncr :: !Assign
+ , _forStmnt :: Statement
+ } -- ^ Loop bounds shall be statically computable for a for loop.
deriving (Eq, Show, Ord, Data)
instance Semigroup Statement where
@@ -350,6 +409,19 @@ instance Semigroup Statement where
instance Monoid Statement where
mempty = SeqBlock []
+-- | Parameter that can be assigned in blocks or modules using @parameter@.
+data Parameter = Parameter { _paramIdent :: {-# UNPACK #-} !Identifier
+ , _paramValue :: ConstExpr
+ }
+ deriving (Eq, Show, Ord, Data)
+
+-- | Local parameter that can be assigned anywhere using @localparam@. It cannot
+-- be changed by initialising the module.
+data LocalParam = LocalParam { _localParamIdent :: {-# UNPACK #-} !Identifier
+ , _localParamValue :: ConstExpr
+ }
+ deriving (Eq, Show, Ord, Data)
+
-- | Module item which is the body of the module expression.
data ModItem = ModCA { _modContAssign :: !ContAssign }
| ModInst { _modInstId :: {-# UNPACK #-} !Identifier
@@ -361,6 +433,8 @@ data ModItem = ModCA { _modContAssign :: !ContAssign }
| Decl { _declDir :: !(Maybe PortDir)
, _declPort :: !Port
}
+ | ParamDecl { _paramDecl :: NonEmpty Parameter }
+ | LocalParamDecl { _localParamDecl :: NonEmpty LocalParam }
deriving (Eq, Show, Ord, Data)
-- | 'module' module_identifier [list_of_ports] ';' { module_item } 'end_module'
@@ -368,7 +442,9 @@ data ModDecl = ModDecl { _modId :: {-# UNPACK #-} !Identifier
, _modOutPorts :: [Port]
, _modInPorts :: [Port]
, _modItems :: [ModItem]
- } deriving (Eq, Show, Ord, Data)
+ , _modParams :: [Parameter]
+ }
+ deriving (Eq, Show, Ord, Data)
traverseModConn :: (Applicative f) => (Expr -> f Expr) -> ModConn -> f ModConn
traverseModConn f (ModConn e ) = ModConn <$> f e
@@ -380,12 +456,8 @@ traverseModItem f (ModInst a b e) =
ModInst a b <$> sequenceA (traverseModConn f <$> e)
traverseModItem _ e = pure e
--- | Description of the Verilog module.
-newtype Description = Description { _getDescription :: ModDecl }
- deriving (Eq, Show, Ord, Data)
-
-- | The complete sourcetext for the Verilog module.
-newtype Verilog = Verilog { _getVerilog :: [Description] }
+newtype Verilog = Verilog { _getVerilog :: [ModDecl] }
deriving (Eq, Show, Ord, Data, Semigroup, Monoid)
makeLenses ''Identifier
@@ -401,12 +473,13 @@ makeLenses ''Assign
makeLenses ''ContAssign
makeLenses ''Statement
makeLenses ''ModItem
+makeLenses ''Parameter
+makeLenses ''LocalParam
makeLenses ''ModDecl
-makeLenses ''Description
makeLenses ''Verilog
getModule :: Traversal' Verilog ModDecl
-getModule = getVerilog . traverse . getDescription
+getModule = getVerilog . traverse
{-# INLINE getModule #-}
getSourceId :: Traversal' Verilog Text
diff --git a/src/VeriFuzz/Verilog/Arbitrary.hs b/src/VeriFuzz/Verilog/Arbitrary.hs
index 72b4cc2..aed548b 100644
--- a/src/VeriFuzz/Verilog/Arbitrary.hs
+++ b/src/VeriFuzz/Verilog/Arbitrary.hs
@@ -48,6 +48,12 @@ instance Arb Identifier where
l <- genPositive
Identifier . T.pack <$> replicateM (l + 1) (Hog.element ['a'..'z'])
+instance Arb Int where
+ arb = Hog.int (Hog.linear 0 100)
+
+instance Arb Integer where
+ arb = integral
+
instance Arb Delay where
arb = Delay <$> genPositive
@@ -140,11 +146,18 @@ exprWithContext l n
| otherwise = exprWithContext l 0
where subexpr y = exprWithContext l (n `div` y)
-instance Arb Int where
- arb = Hog.int (Hog.linear 0 100)
+constExpr :: Gen ConstExpr
+constExpr = Hog.recursive Hog.choice
+ [ ConstNum <$> genPositive <*> arb
+ , ParamId <$> arb
+ ]
+ [ Hog.subtermM constExpr (\e -> ConstUnOp <$> arb <*> pure e)
+ , Hog.subtermM2 constExpr constExpr (\a b -> ConstBinOp <$> pure a <*> arb <*> pure b)
+ , Hog.subterm3 constExpr constExpr constExpr ConstCond
+ ]
instance Arb ConstExpr where
- arb = ConstExpr <$> Hog.int (Hog.linear 0 100)
+ arb = constExpr
instance Arb Task where
arb = Task <$> arb <*> listOf arb
@@ -181,7 +194,6 @@ statement n
| n == 0 = Hog.choice
[ BlockAssign <$> arb
, NonBlockAssign <$> arb
- -- , StatCA <$> arb
, TaskEnable <$> arb
, SysTaskEnable <$> arb
]
@@ -190,7 +202,6 @@ statement n
, SeqBlock <$> listOf1 (substat 4)
, BlockAssign <$> arb
, NonBlockAssign <$> arb
- -- , StatCA <$> arb
, TaskEnable <$> arb
, SysTaskEnable <$> arb
]
@@ -208,11 +219,14 @@ instance Arb ModItem where
modPortGen :: Gen Port
modPortGen = Port <$> arb <*> arb <*> arb <*> arb
-instance Arb ModDecl where
- arb = ModDecl <$> arb <*> listOf arb <*> listOf1 modPortGen <*> listOf arb
+instance Arb Parameter where
+ arb = Parameter <$> arb <*> arb
-instance Arb Description where
- arb = Description <$> arb
+instance Arb LocalParam where
+ arb = LocalParam <$> arb <*> arb
+
+instance Arb ModDecl where
+ arb = ModDecl <$> arb <*> listOf arb <*> listOf1 modPortGen <*> listOf arb <*> listOf arb
instance Arb Verilog where
arb = Verilog <$> listOf1 arb
diff --git a/src/VeriFuzz/Verilog/CodeGen.hs b/src/VeriFuzz/Verilog/CodeGen.hs
index c42c880..8f16b23 100644
--- a/src/VeriFuzz/Verilog/CodeGen.hs
+++ b/src/VeriFuzz/Verilog/CodeGen.hs
@@ -23,6 +23,7 @@ where
import Control.Lens (view, (^.))
import Data.Foldable (fold)
+import Data.List.NonEmpty (NonEmpty (..), toList)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
@@ -45,30 +46,40 @@ defMap = maybe ";\n" statement
-- | Convert the 'Verilog' type to 'Text' so that it can be rendered.
verilogSrc :: Verilog -> Text
-verilogSrc source = fold $ description <$> source ^. getVerilog
-
--- | Generate the 'Description' to 'Text'.
-description :: Description -> Text
-description desc = moduleDecl $ desc ^. getDescription
+verilogSrc (Verilog modules) = fold $ moduleDecl <$> modules
-- | Generate the 'ModDecl' for a module and convert it to 'Text'.
moduleDecl :: ModDecl -> Text
-moduleDecl m =
+moduleDecl (ModDecl i outP inP items ps) =
"module "
- <> m
- ^. modId
- . getIdentifier
- <> ports
- <> ";\n"
- <> modI
+ <> identifier i <> params ps <> ports <> ";\n" <> modI
<> "endmodule\n"
where
- ports | noIn && noOut = ""
+ ports | null outP && null inP = ""
| otherwise = "(" <> comma (modPort <$> outIn) <> ")"
- modI = fold $ moduleItem <$> m ^. modItems
- noOut = null $ m ^. modOutPorts
- noIn = null $ m ^. modInPorts
- outIn = (m ^. modOutPorts) ++ (m ^. modInPorts)
+ modI = fold $ moduleItem <$> items
+ outIn = outP ++ inP
+ params [] = ""
+ params (p:pps) = "#(\n" <> paramList (p :| pps) <> "\n)\n"
+
+-- | Generates a parameter list. Can only be called with a 'NonEmpty' list.
+paramList :: NonEmpty Parameter -> Text
+paramList ps = "parameter " <> (commaNL . toList $ parameter <$> ps)
+
+-- | Generates a localparam list. Can only be called with a 'NonEmpty' list.
+localParamList :: NonEmpty LocalParam -> Text
+localParamList ps = "localparam " <> (commaNL . toList $ localParam <$> ps)
+
+-- | Generates the assignment for a 'Parameter'.
+parameter :: Parameter -> Text
+parameter (Parameter name val) = identifier name <> " = " <> constExpr val
+
+-- | Generates the assignment for a 'LocalParam'.
+localParam :: LocalParam -> Text
+localParam (LocalParam name val) = identifier name <> " = " <> constExpr val
+
+identifier :: Identifier -> Text
+identifier (Identifier i) = i
-- | Conversts 'Port' to 'Text' for the module list, which means it only
-- generates a list of identifiers.
@@ -104,6 +115,8 @@ moduleItem (Initial stat) = "initial " <> statement stat
moduleItem (Always stat) = "always " <> statement stat
moduleItem (Decl dir p ) = maybe "" makePort dir <> port p <> ";\n"
where makePort = (<> " ") . portDir
+moduleItem (ParamDecl p) = paramList p <> ";\n"
+moduleItem (LocalParamDecl p) = localParamList p <> ";\n"
mConn :: ModConn -> Text
mConn (ModConn c ) = expr c
@@ -123,11 +136,7 @@ func UnSignedFunc = "$unsigned"
expr :: Expr -> Text
expr (BinOp eRhs bin eLhs) =
"(" <> expr eRhs <> binaryOp bin <> expr eLhs <> ")"
-expr (Number s n) =
- "(" <> minus <> showT s <> "'h" <> T.pack (showHex (abs n) "") <> ")"
- where
- minus | signum n >= 0 = ""
- | otherwise = "-"
+expr (Number s n) = showNum s n
expr (Id i ) = i ^. getIdentifier
expr (Concat c ) = "{" <> comma (expr <$> c) <> "}"
expr (UnOp u e ) = "(" <> unaryOp u <> expr e <> ")"
@@ -135,6 +144,21 @@ expr (Cond l t f) = "(" <> expr l <> " ? " <> expr t <> " : " <> expr f <> ")"
expr (Func f e ) = func f <> "(" <> expr e <> ")"
expr (Str t ) = "\"" <> t <> "\""
+showNum :: Int -> Integer -> Text
+showNum s n = "(" <> minus <> showT s <> "'h" <> T.pack (showHex (abs n) "") <> ")"
+ where
+ minus | signum n >= 0 = ""
+ | otherwise = "-"
+
+constExpr :: ConstExpr -> Text
+constExpr (ConstNum s n) = showNum s n
+constExpr (ParamId i) = identifier i
+constExpr (ConstConcat c) = "{" <> comma (constExpr <$> c) <> "}"
+constExpr (ConstUnOp u e) = "(" <> unaryOp u <> constExpr e <> ")"
+constExpr (ConstBinOp eRhs bin eLhs) = "(" <> constExpr eRhs <> binaryOp bin <> constExpr eLhs <> ")"
+constExpr (ConstCond l t f) = "(" <> constExpr l <> " ? " <> constExpr t <> " : " <> constExpr f <> ")"
+constExpr (ConstStr t ) = "\"" <> t <> "\""
+
-- | Convert 'BinaryOperator' to 'Text'.
binaryOp :: BinaryOperator -> Text
binaryOp BinPlus = " + "
@@ -197,9 +221,6 @@ lVal (RegSize i msb lsb) =
i ^. getIdentifier <> " [" <> constExpr msb <> ":" <> constExpr lsb <> "]"
lVal (RegConcat e) = "{" <> comma (expr <$> e) <> "}"
-constExpr :: ConstExpr -> Text
-constExpr (ConstExpr num) = showT num
-
pType :: PortType -> Text
pType Wire = "wire"
pType Reg = "reg"
@@ -213,12 +234,15 @@ statement (EventCtrl e stat ) = event e <> " " <> defMap stat
statement (SeqBlock s) = "begin\n" <> fold (statement <$> s) <> "end\n"
statement (BlockAssign a ) = genAssign " = " a <> ";\n"
statement (NonBlockAssign a ) = genAssign " <= " a <> ";\n"
-statement (StatCA a ) = contAssign a
statement (TaskEnable t ) = task t <> ";\n"
statement (SysTaskEnable t ) = "$" <> task t <> ";\n"
statement (CondStmnt e t Nothing) = "if(" <> expr e <> ")\n" <> defMap t
statement (CondStmnt e t f) =
"if(" <> expr e <> ")\n" <> defMap t <> "else\n" <> defMap f
+statement (ForLoop a e incr stmnt) =
+ "for(" <> genAssign " = " a
+ <> "; " <> expr e <> "; " <> genAssign " = " incr
+ <> ")\n" <> statement stmnt
task :: Task -> Text
task (Task name e) | null e = i
@@ -276,9 +300,6 @@ instance Source Port where
instance Source ModDecl where
genSource = moduleDecl
-instance Source Description where
- genSource = description
-
instance Source Verilog where
genSource = verilogSrc
diff --git a/src/VeriFuzz/Verilog/Gen.hs b/src/VeriFuzz/Verilog/Gen.hs
index 3afdd1a..6f50f19 100644
--- a/src/VeriFuzz/Verilog/Gen.hs
+++ b/src/VeriFuzz/Verilog/Gen.hs
@@ -75,7 +75,7 @@ randomMod inps total = do
let other = drop inps ident
let y = ModCA . ContAssign "y" . fold $ Id <$> drop inps ids
let yport = [wire (sumSize other) "y"]
- return . declareMod other . ModDecl "test_module" yport inputs_ $ x ++ [y]
+ return . declareMod other $ ModDecl "test_module" yport inputs_ (x ++ [y]) []
where
ids = toId <$> [1 .. total]
end = drop inps ids
@@ -200,12 +200,12 @@ moduleDef top = do
let clock = Port Wire False 1 "clk"
let yport = Port Wire False size "y"
let comb = combineAssigns_ yport local
- return . declareMod local . ModDecl name [yport] (clock:portList) $ initBlock : mi <> [comb]
+ return . declareMod local $ ModDecl name [yport] (clock:portList) (initBlock : mi <> [comb]) []
-- | Procedural generation method for random Verilog. Uses internal 'Reader' and
-- 'State' to keep track of the current Verilog code structure.
procedural :: Config -> Gen Verilog
-procedural config = Verilog . (: []) . Description <$> Hog.resize
+procedural config = Verilog . (: []) <$> Hog.resize
num
(runReaderT (evalStateT (moduleDef (Just "top")) context) config)
where
diff --git a/src/VeriFuzz/Verilog/Internal.hs b/src/VeriFuzz/Verilog/Internal.hs
index 5999a31..a7b0a15 100644
--- a/src/VeriFuzz/Verilog/Internal.hs
+++ b/src/VeriFuzz/Verilog/Internal.hs
@@ -16,7 +16,7 @@ module VeriFuzz.Verilog.Internal
, emptyMod
, setModName
, addModPort
- , addDescription
+ , addModDecl
, testBench
, addTestBench
, defaultPort
@@ -40,7 +40,7 @@ wireDecl = Decl Nothing . Port Wire False 1
-- | Create an empty module.
emptyMod :: ModDecl
-emptyMod = ModDecl "" [] [] []
+emptyMod = ModDecl "" [] [] [] []
-- | Set a module name for a module declaration.
setModName :: Text -> ModDecl -> ModDecl
@@ -50,8 +50,8 @@ setModName str = modId .~ Identifier str
addModPort :: Port -> ModDecl -> ModDecl
addModPort port = modInPorts %~ (:) port
-addDescription :: Description -> Verilog -> Verilog
-addDescription desc = getVerilog %~ (:) desc
+addModDecl :: ModDecl -> Verilog -> Verilog
+addModDecl desc = getVerilog %~ (:) desc
testBench :: ModDecl
testBench = ModDecl
@@ -75,10 +75,10 @@ testBench = ModDecl
-- ]
-- , SysTaskEnable $ Task "finish" []
]
- ]
+ ] []
addTestBench :: Verilog -> Verilog
-addTestBench = addDescription $ Description testBench
+addTestBench = addModDecl testBench
defaultPort :: Identifier -> Port
defaultPort = Port Wire False 1
diff --git a/src/VeriFuzz/Verilog/Mutate.hs b/src/VeriFuzz/Verilog/Mutate.hs
index 03ee1d0..2b6ab3a 100644
--- a/src/VeriFuzz/Verilog/Mutate.hs
+++ b/src/VeriFuzz/Verilog/Mutate.hs
@@ -72,7 +72,7 @@ idTrans _ _ e = e
-- | Replaces the identifier recursively in an expression.
replace :: Identifier -> Expr -> Expr -> Expr
-replace = (transformOf traverseExpr .) . idTrans
+replace = (transform .) . idTrans
-- | Nest expressions for a specific 'Identifier'. If the 'Identifier' is not
-- found, the AST is not changed.
@@ -107,8 +107,8 @@ allVars m =
-- $setup
-- >>> import VeriFuzz.Verilog.CodeGen
--- >>> let m = (ModDecl (Identifier "m") [Port Wire False 5 (Identifier "y")] [Port Wire False 5 "x"] [])
--- >>> let main = (ModDecl "main" [] [] [])
+-- >>> let m = (ModDecl (Identifier "m") [Port Wire False 5 (Identifier "y")] [Port Wire False 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
@@ -196,7 +196,7 @@ 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 ^. modId) ys (m ^. modInPorts) modIt
+makeTop i m = ModDecl (m ^. modId) ys (m ^. modInPorts) modIt []
where
ys = yPort . flip makeIdFrom "y" <$> [1 .. i]
modIt = instantiateModSpec_ "_" . modN <$> [1 .. i]
diff --git a/src/VeriFuzz/Verilog/Parser.hs b/src/VeriFuzz/Verilog/Parser.hs
index a072ce8..1a954fa 100644
--- a/src/VeriFuzz/Verilog/Parser.hs
+++ b/src/VeriFuzz/Verilog/Parser.hs
@@ -298,14 +298,12 @@ parseModDecl = do
(modPorts PortOut modItem)
(modPorts PortIn modItem)
modItem
-
-parseDescription :: Parser Description
-parseDescription = Description <$> parseModDecl
+ []
-- | Parses a 'String' into 'Verilog' by skipping any beginning whitespace
-- and then parsing multiple Verilog source.
parseVerilogSrc :: Parser Verilog
-parseVerilogSrc = Verilog <$> many parseDescription
+parseVerilogSrc = Verilog <$> many parseModDecl
-- | Parse a 'String' containing verilog code. The parser currently only supports
-- the subset of Verilog that is being generated randomly.
diff --git a/src/VeriFuzz/Verilog/Preprocess.hs b/src/VeriFuzz/Verilog/Preprocess.hs
index fead5f0..6e9305a 100644
--- a/src/VeriFuzz/Verilog/Preprocess.hs
+++ b/src/VeriFuzz/Verilog/Preprocess.hs
@@ -20,7 +20,9 @@ module VeriFuzz.Verilog.Preprocess
)
where
--- | Remove comments from code.
+-- | Remove comments from code. There is no difference between @(* *)@ and
+-- @/* */@, therefore in this implementation, @*/@ could close @(*@ and vice-versa,
+-- This will be fixed in an upcoming version.
uncomment :: FilePath -> String -> String
uncomment file = uncomment'
where
@@ -28,6 +30,7 @@ uncomment file = uncomment'
"" -> ""
'/' : '/' : rest -> " " ++ removeEOL rest
'/' : '*' : rest -> " " ++ remove rest
+ '(' : '*' : rest -> " " ++ remove rest
'"' : rest -> '"' : ignoreString rest
b : rest -> b : uncomment' rest
@@ -43,6 +46,7 @@ uncomment file = uncomment'
'\n' : rest -> '\n' : remove rest
'\t' : rest -> '\t' : remove rest
'*' : '/' : rest -> " " ++ uncomment' rest
+ '*' : ')' : rest -> " " ++ uncomment' rest
_ : rest -> " " ++ remove rest
removeString a = case a of
@@ -105,4 +109,3 @@ ppLine env ('`' : a) = case lookup name env of
a
rest = drop (length name) a
ppLine env (a : b) = a : ppLine env b
-