aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--src/VeriFuzz.hs4
-rw-r--r--src/VeriFuzz/AST.hs18
-rw-r--r--src/VeriFuzz/ASTGen.hs4
-rw-r--r--src/VeriFuzz/CodeGen.hs8
-rw-r--r--src/VeriFuzz/Gen.hs6
-rw-r--r--src/VeriFuzz/Icarus.hs2
-rw-r--r--src/VeriFuzz/Internal/AST.hs6
-rw-r--r--src/VeriFuzz/Internal/Simulator.hs2
-rw-r--r--src/VeriFuzz/Mutate.hs4
-rw-r--r--src/VeriFuzz/Parser.hs5
-rw-r--r--src/VeriFuzz/Parser/Parser.hs21
-rw-r--r--src/VeriFuzz/Yosys.hs2
12 files changed, 42 insertions, 40 deletions
diff --git a/src/VeriFuzz.hs b/src/VeriFuzz.hs
index d07c26e..6099c28 100644
--- a/src/VeriFuzz.hs
+++ b/src/VeriFuzz.hs
@@ -77,7 +77,7 @@ generateByteString n = do
makeSrcInfo :: ModDecl -> SourceInfo
makeSrcInfo m =
- SourceInfo (m ^. modId . getIdentifier) (VerilogSrc [Description m])
+ SourceInfo (m ^. modId . getIdentifier) (Verilog [Description m])
-- | Draw a randomly generated DAG to a dot file and compile it to a png so it
-- can be seen.
@@ -100,7 +100,7 @@ runSimulation = do
-- writeFile "file.dot" dot
-- shelly $ run_ "dot" ["-Tpng", "-o", "file.png", "file.dot"]
-- let circ =
- -- head $ (nestUpTo 30 . generateAST $ Circuit gr) ^.. getVerilogSrc . traverse . getDescription
+ -- head $ (nestUpTo 30 . generateAST $ Circuit gr) ^.. getVerilog . traverse . getDescription
rand <- generateByteString 20
rand2 <- Hog.sample (randomMod 10 100)
val <- shelly $ runSim defaultIcarus (makeSrcInfo rand2) rand
diff --git a/src/VeriFuzz/AST.hs b/src/VeriFuzz/AST.hs
index 0f877f3..1381cc1 100644
--- a/src/VeriFuzz/AST.hs
+++ b/src/VeriFuzz/AST.hs
@@ -16,8 +16,8 @@ Defines the types to build a Verilog AST.
module VeriFuzz.AST
( -- * Top level types
- VerilogSrc(..)
- , getVerilogSrc
+ Verilog(..)
+ , getVerilog
, Description(..)
, getDescription
-- * Primitives
@@ -396,7 +396,7 @@ newtype Description = Description { _getDescription :: ModDecl }
deriving (Eq, Show, Ord, Data)
-- | The complete sourcetext for the Verilog module.
-newtype VerilogSrc = VerilogSrc { _getVerilogSrc :: [Description] }
+newtype Verilog = Verilog { _getVerilog :: [Description] }
deriving (Eq, Show, Ord, Data, Semigroup, Monoid)
makeLenses ''Identifier
@@ -414,13 +414,13 @@ makeLenses ''Statement
makeLenses ''ModItem
makeLenses ''ModDecl
makeLenses ''Description
-makeLenses ''VerilogSrc
+makeLenses ''Verilog
-getModule :: Traversal' VerilogSrc ModDecl
-getModule = getVerilogSrc . traverse . getDescription
+getModule :: Traversal' Verilog ModDecl
+getModule = getVerilog . traverse . getDescription
{-# INLINE getModule #-}
-getSourceId :: Traversal' VerilogSrc Text
+getSourceId :: Traversal' Verilog Text
getSourceId = getModule . modId . getIdentifier
{-# INLINE getSourceId #-}
@@ -610,8 +610,8 @@ instance Arb ModDecl where
instance Arb Description where
arb = Description <$> arb
-instance Arb VerilogSrc where
- arb = VerilogSrc <$> listOf1 arb
+instance Arb Verilog where
+ arb = Verilog <$> listOf1 arb
instance Arb Bool where
arb = Hog.element [True, False]
diff --git a/src/VeriFuzz/ASTGen.hs b/src/VeriFuzz/ASTGen.hs
index 7c295e1..9360a88 100644
--- a/src/VeriFuzz/ASTGen.hs
+++ b/src/VeriFuzz/ASTGen.hs
@@ -75,5 +75,5 @@ genModuleDeclAST c = ModDecl i output ports $ combineAssigns yPort a
a = genAssignAST c
yPort = Port Wire False 90 "y"
-generateAST :: Circuit -> VerilogSrc
-generateAST c = VerilogSrc [Description $ genModuleDeclAST c]
+generateAST :: Circuit -> Verilog
+generateAST c = Verilog [Description $ genModuleDeclAST c]
diff --git a/src/VeriFuzz/CodeGen.hs b/src/VeriFuzz/CodeGen.hs
index 5b27fea..b54d89d 100644
--- a/src/VeriFuzz/CodeGen.hs
+++ b/src/VeriFuzz/CodeGen.hs
@@ -41,9 +41,9 @@ class Source a where
defMap :: Maybe Statement -> Text
defMap = maybe ";\n" statement
--- | Convert the 'VerilogSrc' type to 'Text' so that it can be rendered.
-verilogSrc :: VerilogSrc -> Text
-verilogSrc source = fold $ description <$> source ^. getVerilogSrc
+-- | 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
@@ -277,7 +277,7 @@ instance Source ModDecl where
instance Source Description where
genSource = description
-instance Source VerilogSrc where
+instance Source Verilog where
genSource = verilogSrc
newtype GenVerilog a = GenVerilog { unGenVerilog :: a }
diff --git a/src/VeriFuzz/Gen.hs b/src/VeriFuzz/Gen.hs
index b9545a8..6bc01c9 100644
--- a/src/VeriFuzz/Gen.hs
+++ b/src/VeriFuzz/Gen.hs
@@ -75,7 +75,7 @@ fromGraph = do
$ initMod
. head
$ nestUpTo 5 (generateAST gr)
- ^.. getVerilogSrc
+ ^.. getVerilog
. traverse
. getDescription
@@ -206,8 +206,8 @@ moduleDef top = do
-- | Procedural generation method for random Verilog. Uses internal 'Reader' and
-- 'State' to keep track of the current Verilog code structure.
-procedural :: Config -> Gen VerilogSrc
-procedural config = VerilogSrc . (: []) . Description <$> Hog.resize
+procedural :: Config -> Gen Verilog
+procedural config = Verilog . (: []) . Description <$> Hog.resize
num
(runReaderT (evalStateT (moduleDef True) context) config)
where
diff --git a/src/VeriFuzz/Icarus.hs b/src/VeriFuzz/Icarus.hs
index 32c4013..47159b3 100644
--- a/src/VeriFuzz/Icarus.hs
+++ b/src/VeriFuzz/Icarus.hs
@@ -89,7 +89,7 @@ runSimIcarus sim rinfo bss = do
<> (SysTaskEnable $ Task "finish" [])
]
let newtb = instantiateMod m tb
- let modWithTb = VerilogSrc $ Description <$> [newtb, m]
+ let modWithTb = Verilog $ Description <$> [newtb, m]
writefile "main.v" $ genSource modWithTb
runSimWithFile sim "main.v" bss
where m = rinfo ^. mainModule
diff --git a/src/VeriFuzz/Internal/AST.hs b/src/VeriFuzz/Internal/AST.hs
index 16d40a3..49e1d30 100644
--- a/src/VeriFuzz/Internal/AST.hs
+++ b/src/VeriFuzz/Internal/AST.hs
@@ -34,8 +34,8 @@ setModName str = modId .~ Identifier str
addModPort :: Port -> ModDecl -> ModDecl
addModPort port = modInPorts %~ (:) port
-addDescription :: Description -> VerilogSrc -> VerilogSrc
-addDescription desc = getVerilogSrc %~ (:) desc
+addDescription :: Description -> Verilog -> Verilog
+addDescription desc = getVerilog %~ (:) desc
testBench :: ModDecl
testBench = ModDecl
@@ -61,7 +61,7 @@ testBench = ModDecl
]
]
-addTestBench :: VerilogSrc -> VerilogSrc
+addTestBench :: Verilog -> Verilog
addTestBench = addDescription $ Description testBench
defaultPort :: Identifier -> Port
diff --git a/src/VeriFuzz/Internal/Simulator.hs b/src/VeriFuzz/Internal/Simulator.hs
index 9437fab..4c21864 100644
--- a/src/VeriFuzz/Internal/Simulator.hs
+++ b/src/VeriFuzz/Internal/Simulator.hs
@@ -46,7 +46,7 @@ class (Tool a) => Synthesisor a where
-> Sh () -- ^ does not return any values
data SourceInfo = SourceInfo { runMainModule :: {-# UNPACK #-} !Text
- , runSource :: !VerilogSrc
+ , runSource :: !Verilog
}
deriving (Eq, Show)
diff --git a/src/VeriFuzz/Mutate.hs b/src/VeriFuzz/Mutate.hs
index 4985993..1984805 100644
--- a/src/VeriFuzz/Mutate.hs
+++ b/src/VeriFuzz/Mutate.hs
@@ -67,11 +67,11 @@ nestId i m
def = Id i
-- | Replaces an identifier by a expression in all the module declaration.
-nestSource :: Identifier -> VerilogSrc -> VerilogSrc
+nestSource :: Identifier -> Verilog -> Verilog
nestSource i src = src & getModule %~ nestId i
-- | Nest variables in the format @w[0-9]*@ up to a certain number.
-nestUpTo :: Int -> VerilogSrc -> VerilogSrc
+nestUpTo :: Int -> Verilog -> Verilog
nestUpTo i src =
foldl (flip nestSource) src $ Identifier . fromNode <$> [1 .. i]
diff --git a/src/VeriFuzz/Parser.hs b/src/VeriFuzz/Parser.hs
index 66608f4..d46ecb6 100644
--- a/src/VeriFuzz/Parser.hs
+++ b/src/VeriFuzz/Parser.hs
@@ -11,8 +11,11 @@ Parser module for Verilog.
-}
module VeriFuzz.Parser
- ( module VeriFuzz.Parser.Parser
+ ( parseVerilog
+ , uncomment
+ , preprocess
)
where
import VeriFuzz.Parser.Parser
+import VeriFuzz.Parser.Preprocess
diff --git a/src/VeriFuzz/Parser/Parser.hs b/src/VeriFuzz/Parser/Parser.hs
index 48e92ec..ff0ccdd 100644
--- a/src/VeriFuzz/Parser/Parser.hs
+++ b/src/VeriFuzz/Parser/Parser.hs
@@ -12,18 +12,14 @@ whole Verilog syntax, as the AST does not support it either.
-}
module VeriFuzz.Parser.Parser
- ( -- * Parsers
+ ( -- * Parser
parseVerilog
- , parseVerilogSrc
- , parseDescription
- , parseModDecl
- , parseContAssign
- , parseExpr
)
where
import Control.Lens
import Control.Monad (void)
+import Data.Bifunctor (bimap)
import Data.Functor (($>))
import Data.Functor.Identity (Identity)
import qualified Data.Text as T
@@ -306,12 +302,15 @@ parseModDecl = do
parseDescription :: Parser Description
parseDescription = Description <$> parseModDecl
--- | Parses a 'String' into 'VerilogSrc' by skipping any beginning whitespace
+-- | Parses a 'String' into 'Verilog' by skipping any beginning whitespace
-- and then parsing multiple Verilog source.
-parseVerilogSrc :: Parser VerilogSrc
-parseVerilogSrc = VerilogSrc <$> many parseDescription
+parseVerilogSrc :: Parser Verilog
+parseVerilogSrc = Verilog <$> many parseDescription
-- | Parse a 'String' containing verilog code. The parser currently only supports
-- the subset of Verilog that is being generated randomly.
-parseVerilog :: String -> String -> Either ParseError VerilogSrc
-parseVerilog s = parse parseVerilogSrc s . alexScanTokens . preprocess [] s
+parseVerilog :: String -- ^ Name of parsed object.
+ -> String -- ^ Content to be parsed.
+ -> Either String Verilog -- ^ Returns 'String' with error
+ -- message if parse fails.
+parseVerilog s = bimap show id . parse parseVerilogSrc s . alexScanTokens . preprocess [] s
diff --git a/src/VeriFuzz/Yosys.hs b/src/VeriFuzz/Yosys.hs
index b6da8c2..ef2bc11 100644
--- a/src/VeriFuzz/Yosys.hs
+++ b/src/VeriFuzz/Yosys.hs
@@ -37,7 +37,7 @@ defaultYosys = Yosys "yosys"
writeSimFile
:: Yosys -- ^ Simulator instance
- -> VerilogSrc -- ^ Current Verilog source
+ -> Verilog -- ^ Current Verilog source
-> FilePath -- ^ Output sim file
-> Sh ()
writeSimFile _ src file = do