aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorYann Herklotz <git@ymhg.org>2019-04-02 19:47:32 +0100
committerYann Herklotz <git@ymhg.org>2019-04-02 19:47:32 +0100
commitfd4b0b5152f94cd406f2e5de86ce7ed0a4d2cbd0 (patch)
tree673439d49fa095bf3ae9b7bbbca5f30d7ff20838
parentc0c799ab3f79c370e4c33b8f824489ce8b1c96ec (diff)
downloadverismith-fd4b0b5152f94cd406f2e5de86ce7ed0a4d2cbd0.tar.gz
verismith-fd4b0b5152f94cd406f2e5de86ce7ed0a4d2cbd0.zip
Large refactor with passing tests
-rw-r--r--src/VeriFuzz.hs33
-rw-r--r--src/VeriFuzz/Circuit.hs47
-rw-r--r--src/VeriFuzz/Circuit/Base.hs42
-rw-r--r--src/VeriFuzz/Circuit/Gen.hs (renamed from src/VeriFuzz/ASTGen.hs)20
-rw-r--r--src/VeriFuzz/Circuit/Internal.hs (renamed from src/VeriFuzz/Internal/Circuit.hs)11
-rw-r--r--src/VeriFuzz/Circuit/Random.hs (renamed from src/VeriFuzz/Random.hs)12
-rw-r--r--src/VeriFuzz/Internal.hs13
-rw-r--r--src/VeriFuzz/Parser.hs21
-rw-r--r--src/VeriFuzz/Sim.hs47
-rw-r--r--src/VeriFuzz/Sim/Env.hs (renamed from src/VeriFuzz/Env.hs)26
-rw-r--r--src/VeriFuzz/Sim/Icarus.hs (renamed from src/VeriFuzz/Icarus.hs)49
-rw-r--r--src/VeriFuzz/Sim/Internal.hs (renamed from src/VeriFuzz/Internal/Simulator.hs)20
-rw-r--r--src/VeriFuzz/Sim/Reduce.hs (renamed from src/VeriFuzz/Reduce.hs)33
-rw-r--r--src/VeriFuzz/Sim/Template.hs (renamed from src/VeriFuzz/Internal/Template.hs)24
-rw-r--r--src/VeriFuzz/Sim/XST.hs (renamed from src/VeriFuzz/XST.hs)37
-rw-r--r--src/VeriFuzz/Sim/Yosys.hs (renamed from src/VeriFuzz/Yosys.hs)31
-rw-r--r--src/VeriFuzz/Verilog.hs131
-rw-r--r--src/VeriFuzz/Verilog/AST.hs (renamed from src/VeriFuzz/AST.hs)4
-rw-r--r--src/VeriFuzz/Verilog/CodeGen.hs (renamed from src/VeriFuzz/CodeGen.hs)19
-rw-r--r--src/VeriFuzz/Verilog/Gen.hs (renamed from src/VeriFuzz/Gen.hs)23
-rw-r--r--src/VeriFuzz/Verilog/Internal.hs (renamed from src/VeriFuzz/Internal/AST.hs)24
-rw-r--r--src/VeriFuzz/Verilog/Lex.x (renamed from src/VeriFuzz/Parser/Lex.x)4
-rw-r--r--src/VeriFuzz/Verilog/Mutate.hs (renamed from src/VeriFuzz/Mutate.hs)38
-rw-r--r--src/VeriFuzz/Verilog/Parser.hs (renamed from src/VeriFuzz/Parser/Parser.hs)32
-rw-r--r--src/VeriFuzz/Verilog/Preprocess.hs (renamed from src/VeriFuzz/Parser/Preprocess.hs)4
-rw-r--r--src/VeriFuzz/Verilog/Token.hs (renamed from src/VeriFuzz/Parser/Token.hs)14
-rw-r--r--test/Property.hs13
-rw-r--r--verifuzz.cabal44
28 files changed, 533 insertions, 283 deletions
diff --git a/src/VeriFuzz.hs b/src/VeriFuzz.hs
index 6099c28..310af7d 100644
--- a/src/VeriFuzz.hs
+++ b/src/VeriFuzz.hs
@@ -14,20 +14,10 @@ module VeriFuzz
, runReduce
, draw
, SourceInfo(..)
- , module VeriFuzz.AST
+ , module VeriFuzz.Verilog
, module VeriFuzz.Config
- , module VeriFuzz.ASTGen
, module VeriFuzz.Circuit
- , module VeriFuzz.CodeGen
- , module VeriFuzz.Env
- , module VeriFuzz.Gen
- , module VeriFuzz.Icarus
- , module VeriFuzz.Mutate
- , module VeriFuzz.Parser
- , module VeriFuzz.Random
- , module VeriFuzz.Reduce
- , module VeriFuzz.XST
- , module VeriFuzz.Yosys
+ , module VeriFuzz.Sim
)
where
@@ -46,21 +36,10 @@ import Hedgehog (Gen)
import qualified Hedgehog.Gen as Hog
import Prelude hiding (FilePath)
import Shelly
-import VeriFuzz.AST
-import VeriFuzz.ASTGen
import VeriFuzz.Circuit
-import VeriFuzz.CodeGen
import VeriFuzz.Config
-import VeriFuzz.Env
-import VeriFuzz.Gen
-import VeriFuzz.Icarus
-import VeriFuzz.Internal
-import VeriFuzz.Mutate
-import VeriFuzz.Parser
-import VeriFuzz.Random
-import VeriFuzz.Reduce
-import VeriFuzz.XST
-import VeriFuzz.Yosys
+import VeriFuzz.Sim
+import VeriFuzz.Verilog
-- | Generate a specific number of random bytestrings of size 256.
randomByteString :: C.CtrDRBG -> Int -> [ByteString] -> [ByteString]
@@ -128,7 +107,7 @@ checkEquivalence src dir = shellyFailDir $ do
setenv "VERIFUZZ_ROOT" curr
cd (fromText dir)
catch_sh
- (runEquiv defaultYosys defaultYosys (Just defaultXst) src >> return True
+ (runEquiv defaultYosys defaultYosys (Just defaultXST) src >> return True
)
((\_ -> return False) :: RunFailed -> Sh Bool)
@@ -145,7 +124,7 @@ runEquivalence gm t i = do
setenv "VERIFUZZ_ROOT" curr
cd (fromText "output" </> fromText n)
catch_sh
- ( runEquiv defaultYosys defaultYosys (Just defaultXst) srcInfo
+ ( runEquiv defaultYosys defaultYosys (Just defaultXST) srcInfo
>> echoP "Test OK"
)
$ onFailure n
diff --git a/src/VeriFuzz/Circuit.hs b/src/VeriFuzz/Circuit.hs
index af534a2..37e25ac 100644
--- a/src/VeriFuzz/Circuit.hs
+++ b/src/VeriFuzz/Circuit.hs
@@ -16,28 +16,31 @@ module VeriFuzz.Circuit
, Circuit(..)
, CNode(..)
, CEdge(..)
+ , fromGraph
+ , generateAST
+ , rDups
+ , rDupsCirc
+ , randomDAG
+ , genRandomDAG
)
where
-import Data.Graph.Inductive (Gr, LEdge, LNode)
-import System.Random
-
--- | The types for all the gates.
-data Gate = And
- | Or
- | Xor
- deriving (Show, Eq, Enum, Bounded, Ord)
-
--- | Newtype for the Circuit which implements a Graph from fgl.
-newtype Circuit = Circuit { getCircuit :: Gr Gate () }
-
-newtype CNode = CNode { getCNode :: LNode Gate }
-
-newtype CEdge = CEdge { getCEdge :: LEdge () }
-
-instance Random Gate where
- randomR (a, b) g =
- case randomR (fromEnum a, fromEnum b) g of
- (x, g') -> (toEnum x, g')
-
- random = randomR (minBound, maxBound)
+import Control.Lens
+import Hedgehog (Gen)
+import qualified Hedgehog.Gen as Hog
+import VeriFuzz.Circuit.Base
+import VeriFuzz.Circuit.Gen
+import VeriFuzz.Circuit.Random
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.Mutate
+
+fromGraph :: Gen ModDecl
+fromGraph = do
+ gr <- rDupsCirc <$> Hog.resize 100 randomDAG
+ return
+ $ initMod
+ . head
+ $ nestUpTo 5 (generateAST gr)
+ ^.. getVerilog
+ . traverse
+ . getDescription
diff --git a/src/VeriFuzz/Circuit/Base.hs b/src/VeriFuzz/Circuit/Base.hs
new file mode 100644
index 0000000..6b9f725
--- /dev/null
+++ b/src/VeriFuzz/Circuit/Base.hs
@@ -0,0 +1,42 @@
+{-|
+Module : VeriFuzz.Circuit.Base
+Description : Base types for the circuit module.
+Copyright : (c) 2019, Yann Herklotz Grave
+License : GPL-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Base types for the circuit module.
+-}
+
+module VeriFuzz.Circuit.Base
+ ( Gate(..)
+ , Circuit(..)
+ , CNode(..)
+ , CEdge(..)
+ )
+where
+
+import Data.Graph.Inductive (Gr, LEdge, LNode)
+import System.Random
+
+-- | The types for all the gates.
+data Gate = And
+ | Or
+ | Xor
+ deriving (Show, Eq, Enum, Bounded, Ord)
+
+-- | Newtype for the Circuit which implements a Graph from fgl.
+newtype Circuit = Circuit { getCircuit :: Gr Gate () }
+
+newtype CNode = CNode { getCNode :: LNode Gate }
+
+newtype CEdge = CEdge { getCEdge :: LEdge () }
+
+instance Random Gate where
+ randomR (a, b) g =
+ case randomR (fromEnum a, fromEnum b) g of
+ (x, g') -> (toEnum x, g')
+
+ random = randomR (minBound, maxBound)
diff --git a/src/VeriFuzz/ASTGen.hs b/src/VeriFuzz/Circuit/Gen.hs
index 9360a88..817d2f8 100644
--- a/src/VeriFuzz/ASTGen.hs
+++ b/src/VeriFuzz/Circuit/Gen.hs
@@ -1,16 +1,16 @@
{-|
-Module : VeriFuzz.ASTGen
-Description : Generates the AST from the graph directly.
-Copyright : (c) 2018-2019, Yann Herklotz
-License : BSD-3
+Module : Verilog.Circuit.Gen
+Description : Generate verilog from circuit.
+Copyright : (c) 2019, Yann Herklotz Grave
+License : GPL-3
Maintainer : ymherklotz [at] gmail [dot] com
Stability : experimental
Portability : POSIX
-Generates the AST from the graph directly.
+Generate verilog from circuit.
-}
-module VeriFuzz.ASTGen
+module VeriFuzz.Circuit.Gen
( generateAST
)
where
@@ -18,10 +18,10 @@ where
import Data.Graph.Inductive (LNode, Node)
import qualified Data.Graph.Inductive as G
import Data.Maybe (catMaybes)
-import VeriFuzz.AST
-import VeriFuzz.Circuit
-import VeriFuzz.Internal.Circuit
-import VeriFuzz.Mutate
+import VeriFuzz.Circuit.Base
+import VeriFuzz.Circuit.Internal
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.Mutate
-- | Converts a 'CNode' to an 'Identifier'.
frNode :: Node -> Identifier
diff --git a/src/VeriFuzz/Internal/Circuit.hs b/src/VeriFuzz/Circuit/Internal.hs
index 832d0a4..8a4cf4a 100644
--- a/src/VeriFuzz/Internal/Circuit.hs
+++ b/src/VeriFuzz/Circuit/Internal.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Internal.Circuit
+Module : VeriFuzz.Circuit.Internal
Description : Internal helpers for generation.
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
@@ -10,7 +10,14 @@ Portability : POSIX
Internal helpers for generation.
-}
-module VeriFuzz.Internal.Circuit where
+module VeriFuzz.Circuit.Internal
+ ( fromNode
+ , filterGr
+ , only
+ , inputs
+ , outputs
+ )
+where
import Data.Graph.Inductive (Graph, Node)
import qualified Data.Graph.Inductive as G
diff --git a/src/VeriFuzz/Random.hs b/src/VeriFuzz/Circuit/Random.hs
index 947f74e..58e855c 100644
--- a/src/VeriFuzz/Random.hs
+++ b/src/VeriFuzz/Circuit/Random.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Random
+Module : VeriFuzz.Circuit.Random
Description : Random generation for DAG
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
@@ -10,7 +10,13 @@ Portability : POSIX
Define the random generation for the directed acyclic graph.
-}
-module VeriFuzz.Random where
+module VeriFuzz.Circuit.Random
+ ( rDups
+ , rDupsCirc
+ , randomDAG
+ , genRandomDAG
+ )
+where
import Data.Graph.Inductive (Context)
import qualified Data.Graph.Inductive as G
@@ -19,7 +25,7 @@ import Data.List (nub)
import Hedgehog (Gen)
import qualified Hedgehog.Gen as Hog
import qualified Hedgehog.Range as Hog
-import VeriFuzz.Circuit
+import VeriFuzz.Circuit.Base
dupFolder :: (Eq a, Eq b) => Context a b -> [Context a b] -> [Context a b]
dupFolder cont ns = unique cont : ns
diff --git a/src/VeriFuzz/Internal.hs b/src/VeriFuzz/Internal.hs
index 4f85629..51bb52c 100644
--- a/src/VeriFuzz/Internal.hs
+++ b/src/VeriFuzz/Internal.hs
@@ -15,20 +15,11 @@ module VeriFuzz.Internal
safe
, showT
, comma
- -- * Module Specific Internals
- , module VeriFuzz.Internal.AST
- , module VeriFuzz.Internal.Circuit
- , module VeriFuzz.Internal.Simulator
- , module VeriFuzz.Internal.Template
)
where
-import Data.Text (Text)
-import qualified Data.Text as T
-import VeriFuzz.Internal.AST
-import VeriFuzz.Internal.Circuit
-import VeriFuzz.Internal.Simulator
-import VeriFuzz.Internal.Template
+import Data.Text (Text)
+import qualified Data.Text as T
-- | Converts unsafe list functions in the Prelude to a safe version.
safe :: ([a] -> b) -> [a] -> Maybe b
diff --git a/src/VeriFuzz/Parser.hs b/src/VeriFuzz/Parser.hs
deleted file mode 100644
index d46ecb6..0000000
--- a/src/VeriFuzz/Parser.hs
+++ /dev/null
@@ -1,21 +0,0 @@
-{-|
-Module : VeriFuzz.Parser
-Description : Parser module for Verilog.
-Copyright : (c) 2019, Yann Herklotz Grave
-License : GPL-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Portability : POSIX
-
-Parser module for Verilog.
--}
-
-module VeriFuzz.Parser
- ( parseVerilog
- , uncomment
- , preprocess
- )
-where
-
-import VeriFuzz.Parser.Parser
-import VeriFuzz.Parser.Preprocess
diff --git a/src/VeriFuzz/Sim.hs b/src/VeriFuzz/Sim.hs
new file mode 100644
index 0000000..794d8e9
--- /dev/null
+++ b/src/VeriFuzz/Sim.hs
@@ -0,0 +1,47 @@
+{-|
+Module : VeriFuzz.Sim
+Description : Simulator implementations.
+Copyright : (c) 2019, Yann Herklotz Grave
+License : GPL-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Simulator implementations.
+-}
+
+module VeriFuzz.Sim
+ ( -- * Environment
+ SynthTool(..)
+ , SimTool(..)
+ , SimEnv(..)
+ , SourceInfo(..)
+ , SynthEnv(..)
+ -- * Simulators
+ -- ** Icarus
+ , Icarus(..)
+ , defaultIcarus
+ -- ** XST
+ , XST(..)
+ , defaultXST
+ -- ** Yosys
+ , Yosys(..)
+ , defaultYosys
+ -- * Reducer
+ , reduce
+ -- * Equivalence
+ , runEquiv
+ -- * Simulation
+ , runSim
+ -- * Synthesis
+ , runSynth
+ , echoP
+ )
+where
+
+import VeriFuzz.Sim.Env
+import VeriFuzz.Sim.Icarus
+import VeriFuzz.Sim.Internal
+import VeriFuzz.Sim.Reduce
+import VeriFuzz.Sim.XST
+import VeriFuzz.Sim.Yosys
diff --git a/src/VeriFuzz/Env.hs b/src/VeriFuzz/Sim/Env.hs
index 6448bdf..187afb3 100644
--- a/src/VeriFuzz/Env.hs
+++ b/src/VeriFuzz/Sim/Env.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Env
+Module : VeriFuzz.Sim.Env
Description : Environment to run the simulator and synthesisers in a matrix.
Copyright : (c) 2019, Yann Herklotz
License : GPL-3
@@ -10,25 +10,31 @@ Portability : POSIX
Environment to run the simulator and synthesisers in a matrix.
-}
-module VeriFuzz.Env where
+module VeriFuzz.Sim.Env
+ ( SynthTool(..)
+ , SimTool(..)
+ , SimEnv(..)
+ , SynthEnv(..)
+ )
+where
-import Prelude hiding (FilePath)
+import Prelude hiding (FilePath)
import Shelly
-import VeriFuzz.Icarus
-import VeriFuzz.Internal
-import VeriFuzz.XST
-import VeriFuzz.Yosys
+import VeriFuzz.Sim.Icarus
+import VeriFuzz.Sim.Internal
+import VeriFuzz.Sim.XST
+import VeriFuzz.Sim.Yosys
-data SynthTool = XstSynth {-# UNPACK #-} !Xst
+data SynthTool = XSTSynth {-# UNPACK #-} !XST
| YosysSynth {-# UNPACK #-} !Yosys
deriving (Eq, Show)
instance Tool SynthTool where
- toText (XstSynth xst) = toText xst
+ toText (XSTSynth xst) = toText xst
toText (YosysSynth yosys) = toText yosys
instance Synthesisor SynthTool where
- runSynth (XstSynth xst) = runSynth xst
+ runSynth (XSTSynth xst) = runSynth xst
runSynth (YosysSynth yosys) = runSynth yosys
newtype SimTool = IcarusSim Icarus
diff --git a/src/VeriFuzz/Icarus.hs b/src/VeriFuzz/Sim/Icarus.hs
index 47159b3..6bf21f4 100644
--- a/src/VeriFuzz/Icarus.hs
+++ b/src/VeriFuzz/Sim/Icarus.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Icarus
+Module : VeriFuzz.Sim.Icarus
Description : Icarus verilog module.
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
@@ -10,30 +10,35 @@ Portability : POSIX
Icarus verilog module.
-}
-module VeriFuzz.Icarus where
+module VeriFuzz.Sim.Icarus
+ ( Icarus(..)
+ , defaultIcarus
+ )
+where
import Control.Lens
-import Crypto.Hash (Digest, hash)
-import Crypto.Hash.Algorithms (SHA256)
-import Data.Binary (encode)
-import qualified Data.ByteArray as BA (convert)
-import Data.ByteString (ByteString)
-import qualified Data.ByteString as B
-import Data.ByteString.Lazy (toStrict)
-import qualified Data.ByteString.Lazy as L (ByteString)
-import Data.Char (digitToInt)
-import Data.Foldable (fold)
-import Data.List (transpose)
-import Data.Maybe (listToMaybe)
-import Data.Text (Text)
-import qualified Data.Text as T
-import Numeric (readInt)
-import Prelude hiding (FilePath)
+import Crypto.Hash (Digest, hash)
+import Crypto.Hash.Algorithms (SHA256)
+import Data.Binary (encode)
+import qualified Data.ByteArray as BA (convert)
+import Data.ByteString (ByteString)
+import qualified Data.ByteString as B
+import Data.ByteString.Lazy (toStrict)
+import qualified Data.ByteString.Lazy as L (ByteString)
+import Data.Char (digitToInt)
+import Data.Foldable (fold)
+import Data.List (transpose)
+import Data.Maybe (listToMaybe)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Numeric (readInt)
+import Prelude hiding (FilePath)
import Shelly
-import VeriFuzz.AST
-import VeriFuzz.CodeGen
-import VeriFuzz.Internal
-import VeriFuzz.Mutate
+import VeriFuzz.Sim.Internal
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.CodeGen
+import VeriFuzz.Verilog.Internal
+import VeriFuzz.Verilog.Mutate
data Icarus = Icarus { icarusPath :: FilePath
, vvpPath :: FilePath
diff --git a/src/VeriFuzz/Internal/Simulator.hs b/src/VeriFuzz/Sim/Internal.hs
index 4c21864..e3082b7 100644
--- a/src/VeriFuzz/Internal/Simulator.hs
+++ b/src/VeriFuzz/Sim/Internal.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Internal.Simulator
+Module : VeriFuzz.Sim.Internal
Description : Class of the simulator.
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
@@ -10,7 +10,21 @@ Portability : POSIX
Class of the simulator and the synthesize tool.
-}
-module VeriFuzz.Internal.Simulator where
+module VeriFuzz.Sim.Internal
+ ( Tool(..)
+ , Simulator(..)
+ , Synthesisor(..)
+ , SourceInfo(..)
+ , mainModule
+ , rootPath
+ , timeout
+ , timeout_
+ , bsToI
+ , noPrint
+ , echoP
+ , logger
+ )
+where
import Control.Lens
import Data.Bits (shiftL)
@@ -21,7 +35,7 @@ import qualified Data.Text as T
import Prelude hiding (FilePath)
import Shelly
import System.FilePath.Posix (takeBaseName)
-import VeriFuzz.AST
+import VeriFuzz.Verilog.AST
-- | Tool class.
class Tool a where
diff --git a/src/VeriFuzz/Reduce.hs b/src/VeriFuzz/Sim/Reduce.hs
index 4f1ccea..bed1169 100644
--- a/src/VeriFuzz/Reduce.hs
+++ b/src/VeriFuzz/Sim/Reduce.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Reduce
+Module : VeriFuzz.Sim.Reduce
Description : Test case reducer implementation.
Copyright : (c) 2019, Yann Herklotz
License : GPL-3
@@ -13,16 +13,16 @@ Test case reducer implementation.
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
-module VeriFuzz.Reduce
+module VeriFuzz.Sim.Reduce
( reduce
)
where
import Control.Lens
-import VeriFuzz.AST
-import VeriFuzz.CodeGen
-import VeriFuzz.Internal
-import VeriFuzz.Mutate
+import VeriFuzz.Sim.Internal
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.CodeGen
+import VeriFuzz.Verilog.Mutate
data Replacement a = Dual a a
| Single a
@@ -133,28 +133,17 @@ reduce_
reduce_ repl eval src = do
replAnswer <- sequenceA $ evalIfNotEmpty <$> replacement
case (replacement, replAnswer) of
- (Single s, Single False) -> do
- putStrLn "########## 1 ##########"
- runIf s
- (Dual _ l, Dual True False) -> do
- putStrLn "########## 2 ##########"
- runIf l
- (Dual r _, Dual False True) -> do
- putStrLn "########## 3 ##########"
- runIf r
+ (Single s, Single False) -> runIf s
+ (Dual _ l, Dual True False) -> runIf l
+ (Dual r _, Dual False True) -> runIf r
(Dual r l, Dual False False) -> do
- putStrLn "########## 4 ##########"
lreduced <- runIf l
rreduced <- runIf r
if runSource lreduced < runSource rreduced
then return lreduced
else return rreduced
- (None, None) -> do
- putStrLn "########## 5 ##########"
- return src
- _ -> do
- putStrLn "########## 6 ##########"
- return src
+ (None, None) -> return src
+ _ -> return src
where
replacement = repl src
runIf s = if s /= src then reduce eval s else return s
diff --git a/src/VeriFuzz/Internal/Template.hs b/src/VeriFuzz/Sim/Template.hs
index 1b0e241..5226106 100644
--- a/src/VeriFuzz/Internal/Template.hs
+++ b/src/VeriFuzz/Sim/Template.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Internal.Template
+Module : VeriFuzz.Sim.Template
Description : Template file for different configuration files
Copyright : (c) 2019, Yann Herklotz
License : GPL-3
@@ -12,16 +12,22 @@ Template file for different configuration files.
{-# LANGUAGE QuasiQuotes #-}
-module VeriFuzz.Internal.Template where
+module VeriFuzz.Sim.Template
+ ( yosysSatConfig
+ , yosysSimConfig
+ , xstSynthConfig
+ , sbyConfig
+ )
+where
-import Control.Lens ((^..))
-import Data.Text (Text)
-import qualified Data.Text as T
-import Prelude hiding (FilePath)
+import Control.Lens ((^..))
+import Data.Text (Text)
+import qualified Data.Text as T
+import Prelude hiding (FilePath)
import Shelly
-import Text.Shakespeare.Text (st)
-import VeriFuzz.AST
-import VeriFuzz.Internal.Simulator
+import Text.Shakespeare.Text (st)
+import VeriFuzz.Sim.Internal
+import VeriFuzz.Verilog.AST
rename :: Text -> [Text] -> Text
rename end entries =
diff --git a/src/VeriFuzz/XST.hs b/src/VeriFuzz/Sim/XST.hs
index 3f4f6c3..359b587 100644
--- a/src/VeriFuzz/XST.hs
+++ b/src/VeriFuzz/Sim/XST.hs
@@ -1,41 +1,46 @@
{-|
-Module : VeriFuzz.XST
-Description : Xst (ise) simulator implementation.
+Module : VeriFuzz.Sim.XST
+Description : XST (ise) simulator implementation.
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
Maintainer : ymherklotz [at] gmail [dot] com
Stability : experimental
Portability : POSIX
-Xst (ise) simulator implementation.
+XST (ise) simulator implementation.
-}
{-# LANGUAGE QuasiQuotes #-}
-module VeriFuzz.XST where
+module VeriFuzz.Sim.XST
+ ( XST(..)
+ , defaultXST
+ )
+where
-import Prelude hiding (FilePath)
+import Prelude hiding (FilePath)
import Shelly
-import Text.Shakespeare.Text (st)
-import VeriFuzz.CodeGen
-import VeriFuzz.Internal
+import Text.Shakespeare.Text (st)
+import VeriFuzz.Sim.Internal
+import VeriFuzz.Sim.Template
+import VeriFuzz.Verilog.CodeGen
-data Xst = Xst { xstPath :: {-# UNPACK #-} !FilePath
+data XST = XST { xstPath :: {-# UNPACK #-} !FilePath
, netgenPath :: {-# UNPACK #-} !FilePath
}
deriving (Eq, Show)
-instance Tool Xst where
+instance Tool XST where
toText _ = "xst"
-instance Synthesisor Xst where
- runSynth = runSynthXst
+instance Synthesisor XST where
+ runSynth = runSynthXST
-defaultXst :: Xst
-defaultXst = Xst "xst" "netgen"
+defaultXST :: XST
+defaultXST = XST "xst" "netgen"
-runSynthXst :: Xst -> SourceInfo -> FilePath -> Sh ()
-runSynthXst sim (SourceInfo top src) outf = do
+runSynthXST :: XST -> SourceInfo -> FilePath -> Sh ()
+runSynthXST sim (SourceInfo top src) outf = do
dir <- pwd
writefile xstFile $ xstSynthConfig top
writefile prjFile [st|verilog work "rtl.v"|]
diff --git a/src/VeriFuzz/Yosys.hs b/src/VeriFuzz/Sim/Yosys.hs
index ef2bc11..0d0c98b 100644
--- a/src/VeriFuzz/Yosys.hs
+++ b/src/VeriFuzz/Sim/Yosys.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Yosys
+Module : VeriFuzz.Sim.Yosys
Description : Yosys simulator implementation.
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
@@ -12,16 +12,22 @@ Yosys simulator implementation.
{-# LANGUAGE QuasiQuotes #-}
-module VeriFuzz.Yosys where
+module VeriFuzz.Sim.Yosys
+ ( Yosys(..)
+ , defaultYosys
+ , runEquiv
+ , runEquivYosys
+ )
+where
import Control.Lens
-import Prelude hiding (FilePath)
+import Prelude hiding (FilePath)
import Shelly
-import Text.Shakespeare.Text (st)
-import VeriFuzz.AST
-import VeriFuzz.CodeGen
-import VeriFuzz.Internal
-import VeriFuzz.Mutate
+import Text.Shakespeare.Text (st)
+import VeriFuzz.Sim.Internal
+import VeriFuzz.Sim.Template
+import VeriFuzz.Verilog.CodeGen
+import VeriFuzz.Verilog.Mutate
newtype Yosys = Yosys { yosysPath :: FilePath }
deriving (Eq, Show)
@@ -35,15 +41,6 @@ instance Synthesisor Yosys where
defaultYosys :: Yosys
defaultYosys = Yosys "yosys"
-writeSimFile
- :: Yosys -- ^ Simulator instance
- -> Verilog -- ^ Current Verilog source
- -> FilePath -- ^ Output sim file
- -> Sh ()
-writeSimFile _ src file = do
- writefile "rtl.v" $ genSource src
- writefile file yosysSimConfig
-
runSynthYosys :: Yosys -> SourceInfo -> FilePath -> Sh ()
runSynthYosys sim (SourceInfo _ src) outf = do
dir <- pwd
diff --git a/src/VeriFuzz/Verilog.hs b/src/VeriFuzz/Verilog.hs
new file mode 100644
index 0000000..fdf2ac0
--- /dev/null
+++ b/src/VeriFuzz/Verilog.hs
@@ -0,0 +1,131 @@
+{-|
+Module : VeriFuzz.Verilog
+Description : Verilog implementation with random generation and mutations.
+Copyright : (c) 2019, Yann Herklotz Grave
+License : GPL-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Verilog implementation with random generation and mutations.
+-}
+
+module VeriFuzz.Verilog
+ ( Verilog(..)
+ , parseVerilog
+ , procedural
+ , randomMod
+ , GenVerilog(..)
+ , genSource
+ , getVerilog
+ , Description(..)
+ , getDescription
+ -- * Primitives
+ -- ** Identifier
+ , Identifier(..)
+ , getIdentifier
+ -- ** Control
+ , Delay(..)
+ , getDelay
+ , Event(..)
+ -- ** Operators
+ , BinaryOperator(..)
+ , UnaryOperator(..)
+ -- ** Task
+ , Task(..)
+ , taskName
+ , taskExpr
+ -- ** Left hand side value
+ , LVal(..)
+ , regId
+ , regExprId
+ , regExpr
+ , regSizeId
+ , regSizeMSB
+ , regSizeLSB
+ , regConc
+ -- ** Ports
+ , PortDir(..)
+ , PortType(..)
+ , Port(..)
+ , portType
+ , portSigned
+ , portSize
+ , portName
+ -- * Expression
+ , Expr(..)
+ , exprSize
+ , exprVal
+ , exprId
+ , exprConcat
+ , exprUnOp
+ , exprPrim
+ , exprLhs
+ , exprBinOp
+ , exprRhs
+ , exprCond
+ , exprTrue
+ , exprFalse
+ , exprFunc
+ , exprBody
+ , exprStr
+ , exprWithContext
+ , traverseExpr
+ , ConstExpr(..)
+ , constNum
+ , Function(..)
+ -- * Assignment
+ , Assign(..)
+ , assignReg
+ , assignDelay
+ , assignExpr
+ , ContAssign(..)
+ , contAssignNetLVal
+ , contAssignExpr
+ -- * Statment
+ , Statement(..)
+ , statDelay
+ , statDStat
+ , statEvent
+ , statEStat
+ , statements
+ , stmntBA
+ , stmntNBA
+ , stmntCA
+ , stmntTask
+ , stmntSysTask
+ , stmntCondExpr
+ , stmntCondTrue
+ , stmntCondFalse
+ -- * Module
+ , ModDecl(..)
+ , modId
+ , modOutPorts
+ , modInPorts
+ , modItems
+ , ModItem(..)
+ , modContAssign
+ , modInstId
+ , modInstName
+ , modInstConns
+ , traverseModItem
+ , declDir
+ , declPort
+ , ModConn(..)
+ , modConn
+ , modConnName
+ , modExpr
+ -- * Useful Lenses and Traversals
+ , getModule
+ , getSourceId
+ -- * Arbitrary
+ , Arb
+ , arb
+ , genPositive
+ )
+where
+
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.CodeGen
+import VeriFuzz.Verilog.Gen
+import VeriFuzz.Verilog.Parser
diff --git a/src/VeriFuzz/AST.hs b/src/VeriFuzz/Verilog/AST.hs
index 1381cc1..405b712 100644
--- a/src/VeriFuzz/AST.hs
+++ b/src/VeriFuzz/Verilog/AST.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.AST
+Module : VeriFuzz.Verilog.AST
Description : Definition of the Verilog AST types.
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
@@ -14,7 +14,7 @@ Defines the types to build a Verilog AST.
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
-module VeriFuzz.AST
+module VeriFuzz.Verilog.AST
( -- * Top level types
Verilog(..)
, getVerilog
diff --git a/src/VeriFuzz/CodeGen.hs b/src/VeriFuzz/Verilog/CodeGen.hs
index b54d89d..eb3b3d1 100644
--- a/src/VeriFuzz/CodeGen.hs
+++ b/src/VeriFuzz/Verilog/CodeGen.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.CodeGen
+Module : VeriFuzz.Verilog.CodeGen
Description : Code generation for Verilog AST.
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
@@ -13,7 +13,7 @@ This module generates the code from the Verilog AST defined in
{-# LANGUAGE FlexibleInstances #-}
-module VeriFuzz.CodeGen
+module VeriFuzz.Verilog.CodeGen
( -- * Code Generation
GenVerilog(..)
, genSource
@@ -21,14 +21,15 @@ module VeriFuzz.CodeGen
)
where
-import Control.Lens (view, (^.))
-import Data.Foldable (fold)
-import Data.Text (Text)
-import qualified Data.Text as T
-import qualified Data.Text.IO as T
-import Numeric (showHex)
-import VeriFuzz.AST
+import Control.Lens (view, (^.))
+import Data.Foldable (fold)
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.Text.IO as T
+import Numeric (showHex)
import VeriFuzz.Internal
+import VeriFuzz.Sim.Internal
+import VeriFuzz.Verilog.AST
-- | '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
diff --git a/src/VeriFuzz/Gen.hs b/src/VeriFuzz/Verilog/Gen.hs
index 6bc01c9..3d508c6 100644
--- a/src/VeriFuzz/Gen.hs
+++ b/src/VeriFuzz/Verilog/Gen.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Gen
+Module : VeriFuzz.Verilog.Gen
Description : Various useful generators.
Copyright : (c) 2019, Yann Herklotz
License : GPL-3
@@ -12,10 +12,9 @@ Various useful generators.
{-# LANGUAGE TemplateHaskell #-}
-module VeriFuzz.Gen
+module VeriFuzz.Verilog.Gen
( -- * Generation methods
procedural
- , fromGraph
, randomMod
)
where
@@ -29,12 +28,11 @@ import Data.Foldable (fold)
import qualified Data.Text as T
import Hedgehog (Gen)
import qualified Hedgehog.Gen as Hog
-import VeriFuzz.AST
-import VeriFuzz.ASTGen
import VeriFuzz.Config
import VeriFuzz.Internal
-import VeriFuzz.Mutate
-import VeriFuzz.Random
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.Internal
+import VeriFuzz.Verilog.Mutate
data Context = Context { _variables :: [Port]
, _nameCounter :: Int
@@ -68,17 +66,6 @@ randomOrdAssigns :: [Identifier] -> [Identifier] -> [Gen ModItem]
randomOrdAssigns inp ids = snd $ foldr generate (inp, []) ids
where generate cid (i, o) = (cid : i, random i (ContAssign cid) : o)
-fromGraph :: Gen ModDecl
-fromGraph = do
- gr <- rDupsCirc <$> Hog.resize 100 randomDAG
- return
- $ initMod
- . head
- $ nestUpTo 5 (generateAST gr)
- ^.. getVerilog
- . traverse
- . getDescription
-
randomMod :: Int -> Int -> Gen ModDecl
randomMod inps total = do
x <- sequence $ randomOrdAssigns start end
diff --git a/src/VeriFuzz/Internal/AST.hs b/src/VeriFuzz/Verilog/Internal.hs
index 49e1d30..5999a31 100644
--- a/src/VeriFuzz/Internal/AST.hs
+++ b/src/VeriFuzz/Verilog/Internal.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Internal.AST
+Module : VeriFuzz.Verilog.Internal
Description : Defaults and common functions.
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
@@ -10,11 +10,27 @@ Portability : POSIX
Defaults and common functions.
-}
-module VeriFuzz.Internal.AST where
+module VeriFuzz.Verilog.Internal
+ ( regDecl
+ , wireDecl
+ , emptyMod
+ , setModName
+ , addModPort
+ , addDescription
+ , testBench
+ , addTestBench
+ , defaultPort
+ , portToExpr
+ , modName
+ , yPort
+ , wire
+ , reg
+ )
+where
import Control.Lens
-import Data.Text (Text)
-import VeriFuzz.AST
+import Data.Text (Text)
+import VeriFuzz.Verilog.AST
regDecl :: Identifier -> ModItem
regDecl = Decl Nothing . Port Reg False 1
diff --git a/src/VeriFuzz/Parser/Lex.x b/src/VeriFuzz/Verilog/Lex.x
index 86c431e..2e99698 100644
--- a/src/VeriFuzz/Parser/Lex.x
+++ b/src/VeriFuzz/Verilog/Lex.x
@@ -1,10 +1,10 @@
{
{-# OPTIONS_GHC -w #-}
-module VeriFuzz.Parser.Lex
+module VeriFuzz.Verilog.Lex
( alexScanTokens
) where
-import VeriFuzz.Parser.Token
+import VeriFuzz.Verilog.Token
}
diff --git a/src/VeriFuzz/Mutate.hs b/src/VeriFuzz/Verilog/Mutate.hs
index 1984805..c72463f 100644
--- a/src/VeriFuzz/Mutate.hs
+++ b/src/VeriFuzz/Verilog/Mutate.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Mutation
+Module : VeriFuzz.Verilog.Mutate
Description : Functions to mutate the Verilog AST.
Copyright : (c) 2018-2019, Yann Herklotz
License : BSD-3
@@ -11,15 +11,39 @@ 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.Mutate where
+module VeriFuzz.Verilog.Mutate
+ ( inPort
+ , findAssign
+ , idTrans
+ , replace
+ , nestId
+ , nestSource
+ , nestUpTo
+ , allVars
+ , instantiateMod
+ , instantiateMod_
+ , instantiateModSpec_
+ , filterChar
+ , initMod
+ , makeIdFrom
+ , makeTop
+ , makeTopAssert
+ , simplify
+ , removeId
+ , combineAssigns
+ , declareMod
+ )
+where
import Control.Lens
-import Data.Foldable (fold)
-import Data.Maybe (catMaybes, fromMaybe)
-import Data.Text (Text)
-import qualified Data.Text as T
-import VeriFuzz.AST
+import Data.Foldable (fold)
+import Data.Maybe (catMaybes, fromMaybe)
+import Data.Text (Text)
+import qualified Data.Text as T
+import VeriFuzz.Circuit.Internal
import VeriFuzz.Internal
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.Internal
-- | Return if the 'Identifier' is in a 'ModDecl'.
inPort :: Identifier -> ModDecl -> Bool
diff --git a/src/VeriFuzz/Parser/Parser.hs b/src/VeriFuzz/Verilog/Parser.hs
index ff0ccdd..5e8bb55 100644
--- a/src/VeriFuzz/Parser/Parser.hs
+++ b/src/VeriFuzz/Verilog/Parser.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Parser.Parser
+Module : VeriFuzz.Verilog.Parser
Description : Minimal Verilog parser to reconstruct the AST.
Copyright : (c) 2019, Yann Herklotz
License : GPL-3
@@ -11,28 +11,28 @@ Minimal Verilog parser to reconstruct the AST. This parser does not support the
whole Verilog syntax, as the AST does not support it either.
-}
-module VeriFuzz.Parser.Parser
+module VeriFuzz.Verilog.Parser
( -- * Parser
parseVerilog
+ , parseModDecl
)
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
-import Text.Parsec hiding (satisfy)
-import Text.Parsec.Expr
-import VeriFuzz.AST
---import VeriFuzz.CodeGen
+import Control.Monad (void)
+import Data.Bifunctor (bimap)
import Data.Bits
-import Data.List (isInfixOf, isPrefixOf)
-import VeriFuzz.Internal
-import VeriFuzz.Parser.Lex
-import VeriFuzz.Parser.Preprocess
-import VeriFuzz.Parser.Token
+import Data.Functor (($>))
+import Data.Functor.Identity (Identity)
+import Data.List (isInfixOf, isPrefixOf)
+import qualified Data.Text as T
+import Text.Parsec hiding (satisfy)
+import Text.Parsec.Expr
+import VeriFuzz.Verilog.AST
+import VeriFuzz.Verilog.Internal
+import VeriFuzz.Verilog.Lex
+import VeriFuzz.Verilog.Preprocess
+import VeriFuzz.Verilog.Token
type Parser = Parsec [Token] ()
diff --git a/src/VeriFuzz/Parser/Preprocess.hs b/src/VeriFuzz/Verilog/Preprocess.hs
index 1483a83..fead5f0 100644
--- a/src/VeriFuzz/Parser/Preprocess.hs
+++ b/src/VeriFuzz/Verilog/Preprocess.hs
@@ -1,5 +1,5 @@
{-|
-Module : VeriFuzz.Parser.Preprocess
+Module : VeriFuzz.Verilog.Preprocess
Description : Simple preprocessor for `define and comments.
Copyright : (c) 2011-2015 Tom Hawkins, 2019 Yann Herklotz
License : GPL-3
@@ -14,7 +14,7 @@ The code is from https://github.com/tomahawkins/verilog.
Edits to the original code are warning fixes and formatting changes.
-}
-module VeriFuzz.Parser.Preprocess
+module VeriFuzz.Verilog.Preprocess
( uncomment
, preprocess
)
diff --git a/src/VeriFuzz/Parser/Token.hs b/src/VeriFuzz/Verilog/Token.hs
index 811331b..65c2319 100644
--- a/src/VeriFuzz/Parser/Token.hs
+++ b/src/VeriFuzz/Verilog/Token.hs
@@ -1,4 +1,16 @@
-module VeriFuzz.Parser.Token
+{-|
+Module : VeriFuzz.Verilog.Token
+Description : Tokens for Verilog parsing.
+Copyright : (c) 2019, Yann Herklotz Grave
+License : GPL-3
+Maintainer : ymherklotz [at] gmail [dot] com
+Stability : experimental
+Portability : POSIX
+
+Tokens for Verilog parsing.
+-}
+
+module VeriFuzz.Verilog.Token
( Token(..)
, TokenName(..)
, Position(..)
diff --git a/test/Property.hs b/test/Property.hs
index be8132b..ba961cf 100644
--- a/test/Property.hs
+++ b/test/Property.hs
@@ -3,16 +3,17 @@ module Property
)
where
-import Data.Either (fromRight, isRight)
-import qualified Data.Graph.Inductive as G
-import Hedgehog (Gen, (===))
-import qualified Hedgehog as Hog
-import qualified Hedgehog.Gen as Hog
+import Data.Either (fromRight, isRight)
+import qualified Data.Graph.Inductive as G
+import Hedgehog (Gen, (===))
+import qualified Hedgehog as Hog
+import qualified Hedgehog.Gen as Hog
import Test.Tasty
import Test.Tasty.Hedgehog
import Text.Parsec
import VeriFuzz
-import VeriFuzz.Parser.Lex
+import VeriFuzz.Verilog.Lex
+import VeriFuzz.Verilog.Parser
randomMod' :: Gen ModDecl
randomMod' = Hog.resize 20 (randomMod 3 10)
diff --git a/verifuzz.cabal b/verifuzz.cabal
index 9e4a5a6..7830465 100644
--- a/verifuzz.cabal
+++ b/verifuzz.cabal
@@ -28,29 +28,31 @@ library
ghc-options: -Wall -Werror
build-tools: alex >=3 && <4
exposed-modules: VeriFuzz
- , VeriFuzz.AST
+ , VeriFuzz.Circuit
+ , VeriFuzz.Circuit.Base
+ , VeriFuzz.Circuit.Gen
+ , VeriFuzz.Circuit.Internal
+ , VeriFuzz.Circuit.Random
, VeriFuzz.Config
, VeriFuzz.Internal
- , VeriFuzz.Internal.AST
- , VeriFuzz.Internal.Circuit
- , VeriFuzz.Internal.Simulator
- , VeriFuzz.Internal.Template
- , VeriFuzz.ASTGen
- , VeriFuzz.Circuit
- , VeriFuzz.CodeGen
- , VeriFuzz.Env
- , VeriFuzz.Gen
- , VeriFuzz.Icarus
- , VeriFuzz.Mutate
- , VeriFuzz.Parser
- , VeriFuzz.Parser.Parser
- , VeriFuzz.Parser.Preprocess
- , VeriFuzz.Parser.Token
- , VeriFuzz.Parser.Lex
- , VeriFuzz.Random
- , VeriFuzz.Reduce
- , VeriFuzz.XST
- , VeriFuzz.Yosys
+ , VeriFuzz.Sim
+ , VeriFuzz.Sim.Env
+ , VeriFuzz.Sim.Icarus
+ , VeriFuzz.Sim.Internal
+ , VeriFuzz.Sim.Reduce
+ , VeriFuzz.Sim.Template
+ , VeriFuzz.Sim.XST
+ , VeriFuzz.Sim.Yosys
+ , VeriFuzz.Verilog
+ , VeriFuzz.Verilog.AST
+ , VeriFuzz.Verilog.CodeGen
+ , VeriFuzz.Verilog.Gen
+ , VeriFuzz.Verilog.Internal
+ , VeriFuzz.Verilog.Lex
+ , VeriFuzz.Verilog.Mutate
+ , VeriFuzz.Verilog.Parser
+ , VeriFuzz.Verilog.Preprocess
+ , VeriFuzz.Verilog.Token
build-depends: base >=4.7 && <5
, hedgehog >= 0.6 && <0.7
, fgl >=5.7 && <5.8