aboutsummaryrefslogtreecommitdiffstats
path: root/src/VeriFuzz
diff options
context:
space:
mode:
authorYann Herklotz <git@ymhg.org>2019-05-07 19:40:32 +0100
committerYann Herklotz <git@ymhg.org>2019-05-07 19:40:32 +0100
commitdb5c1a788e86d52b75ac237270bf2cabcbd296e6 (patch)
tree4b8695f821d93e45cba71fd1eab5e7f0ffb75df4 /src/VeriFuzz
parent634315880f01c65d916d53db12f92b49517fab9f (diff)
downloadverismith-db5c1a788e86d52b75ac237270bf2cabcbd296e6.tar.gz
verismith-db5c1a788e86d52b75ac237270bf2cabcbd296e6.zip
Add description field to Yosys
Diffstat (limited to 'src/VeriFuzz')
-rw-r--r--src/VeriFuzz/Fuzz.hs7
-rw-r--r--src/VeriFuzz/Sim/Yosys.hs17
2 files changed, 12 insertions, 12 deletions
diff --git a/src/VeriFuzz/Fuzz.hs b/src/VeriFuzz/Fuzz.hs
index c1bbfe4..7390aee 100644
--- a/src/VeriFuzz/Fuzz.hs
+++ b/src/VeriFuzz/Fuzz.hs
@@ -138,15 +138,14 @@ pop f a = do
equivalence :: (MonadBaseControl IO m, MonadSh m) => SourceInfo -> Fuzz m ()
equivalence src = do
- yos <- lift $ asks yosysInstance
synth <- passedSynthesis
let synthComb =
nubBy tupEq . filter (uncurry (/=)) $ combinations synth synth
- results <- liftSh $ mapM (uncurry $ equiv yos) synthComb
+ results <- liftSh $ mapM (uncurry equiv) synthComb
liftSh $ inspect results
where
tupEq (a, b) (a', b') = (a == a' && b == b') || (a == b' && b == a')
- equiv yos a b = runResultT $ do
+ equiv a b = runResultT $ do
make dir
pop dir $ do
liftSh $ do
@@ -155,7 +154,7 @@ equivalence src = do
cp (fromText ".." </> fromText (toText b) </> synthOutput b)
$ synthOutput b
writefile "rtl.v" $ genSource src
- runEquiv yos a (Just b) src
+ runEquiv a (Just b) src
where dir = fromText $ "equiv_" <> toText a <> "_" <> toText b
fuzz :: MonadFuzz m => Gen SourceInfo -> Config -> Fuzz m FuzzReport
diff --git a/src/VeriFuzz/Sim/Yosys.hs b/src/VeriFuzz/Sim/Yosys.hs
index 656bc52..50c9759 100644
--- a/src/VeriFuzz/Sim/Yosys.hs
+++ b/src/VeriFuzz/Sim/Yosys.hs
@@ -21,6 +21,7 @@ module VeriFuzz.Sim.Yosys
where
import Control.Lens
+import Data.Text
import Prelude hiding (FilePath)
import Shelly
import Shelly.Lifted (liftSh)
@@ -31,24 +32,25 @@ import VeriFuzz.Verilog.AST
import VeriFuzz.Verilog.CodeGen
import VeriFuzz.Verilog.Mutate
-data Yosys = Yosys { yosysPath :: {-# UNPACK #-} !FilePath
- , yosysOutput :: {-# UNPACK #-} !FilePath
+data Yosys = Yosys { yosysPath :: {-# UNPACK #-} !FilePath
+ , yosysDescription :: {-# UNPACK #-} !Text
+ , yosysOutput :: {-# UNPACK #-} !FilePath
}
deriving (Eq)
instance Tool Yosys where
- toText _ = "yosys"
+ toText (Yosys _ t _) = t
instance Synthesiser Yosys where
runSynth = runSynthYosys
synthOutput = yosysOutput
- setSynthOutput (Yosys a _) = Yosys a
+ setSynthOutput (Yosys a b _) = Yosys a b
instance Show Yosys where
show _ = "yosys"
defaultYosys :: Yosys
-defaultYosys = Yosys "yosys" "syn_yosys.v"
+defaultYosys = Yosys "yosys" "syn_yosys.v" "yosys"
runSynthYosys :: Yosys -> SourceInfo -> ResultSh ()
runSynthYosys sim (SourceInfo _ src) = (<?> SynthFail) . liftSh $ do
@@ -98,12 +100,11 @@ runEquivYosys yosys sim1 sim2 srcInfo = do
runEquiv
:: (Synthesiser a, Synthesiser b)
- => Yosys
- -> a
+ => a
-> Maybe b
-> SourceInfo
-> ResultSh ()
-runEquiv _ sim1 sim2 srcInfo = do
+runEquiv sim1 sim2 srcInfo = do
dir <- liftSh pwd
liftSh $ do
writefile "top.v"