aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--app/Main.hs16
-rw-r--r--src/VeriFuzz/Simulator/General.hs4
-rw-r--r--src/VeriFuzz/Simulator/Icarus.hs2
-rw-r--r--src/VeriFuzz/Simulator/Xst.hs8
-rw-r--r--src/VeriFuzz/Simulator/Yosys.hs6
5 files changed, 23 insertions, 13 deletions
diff --git a/app/Main.hs b/app/Main.hs
index 76fe45c..aeda6a6 100644
--- a/app/Main.hs
+++ b/app/Main.hs
@@ -13,6 +13,12 @@ import Shelly
import qualified Test.QuickCheck as QC
import VeriFuzz
+myForkIO :: IO () -> IO (MVar ())
+myForkIO io = do
+ mvar <- newEmptyMVar
+ _ <- forkFinally io (\_ -> putMVar mvar ())
+ return mvar
+
genRand :: C.CtrDRBG -> Int -> [ByteString] -> [ByteString]
genRand gen n bytes | n == 0 = ranBytes : bytes
| otherwise = genRand newGen (n - 1) $ ranBytes : bytes
@@ -57,14 +63,14 @@ runEquivalence t i = do
cd (fromText "equiv" </> fromText n)
catch_sh (runEquiv defaultYosys defaultYosys (Just defaultXst) circ) $ onFailure n
cd ".."
- runEquivalence t $ i+1
+ --runEquivalence t $ i+1
where
n = t <> "_" <> T.pack (show i)
main :: IO ()
--main = sample (arbitrary :: Gen (Circuit Input))
main = do
- _ <- forkIO $ runEquivalence "test_1" 0
- _ <- forkIO $ runEquivalence "test_2" 0
- _ <- forkIO $ runEquivalence "test_3" 0
- runEquivalence "test_4" 0
+ num <- getNumCapabilities
+ vars <- sequence $ (\x -> myForkIO $
+ runEquivalence ("test_" <> T.pack (show x)) 0) <$> [1..num]
+ sequence_ $ takeMVar <$> vars
diff --git a/src/VeriFuzz/Simulator/General.hs b/src/VeriFuzz/Simulator/General.hs
index 538ecaa..543c139 100644
--- a/src/VeriFuzz/Simulator/General.hs
+++ b/src/VeriFuzz/Simulator/General.hs
@@ -55,3 +55,7 @@ timeout_ = command1_ "timeout" ["180"] . toTextIgnore
bsToI :: ByteString -> Integer
bsToI = B.foldl' (\i b -> (i `shiftL` 8) + fromIntegral b) 0
{-# INLINE bsToI #-}
+
+noPrint :: Sh a -> Sh a
+noPrint =
+ print_stdout False . print_stderr False
diff --git a/src/VeriFuzz/Simulator/Icarus.hs b/src/VeriFuzz/Simulator/Icarus.hs
index 4782585..3518447 100644
--- a/src/VeriFuzz/Simulator/Icarus.hs
+++ b/src/VeriFuzz/Simulator/Icarus.hs
@@ -58,5 +58,5 @@ runSimIcarus sim m bss = do
let newtb = instantiateMod m tb
let modWithTb = VerilogSrc $ Description <$> [newtb, m]
writefile "main.v" $ genSource modWithTb
- run_ (icarusPath sim) ["-o", "main", "main.v"]
+ noPrint $ run_ (icarusPath sim) ["-o", "main", "main.v"]
hash <$> run (vvpPath sim) ["main"]
diff --git a/src/VeriFuzz/Simulator/Xst.hs b/src/VeriFuzz/Simulator/Xst.hs
index 415a45e..03c1707 100644
--- a/src/VeriFuzz/Simulator/Xst.hs
+++ b/src/VeriFuzz/Simulator/Xst.hs
@@ -42,10 +42,10 @@ runSynthXst sim m outf = do
writefile xstFile $ xstSynthConfig m
writefile prjFile [st|verilog work "rtl.v"|]
writefile "rtl.v" $ genSource m
- timeout_ (xstPath sim) ["-ifn", toTextIgnore xstFile]
- run_ (netgenPath sim)
- ["-w", "-ofmt", "verilog", toTextIgnore $ modFile <.> "ngc", toTextIgnore outf]
- run_ "sed" ["-i", "/^`ifndef/,/^`endif/ d; s/ *Timestamp: .*//;", toTextIgnore outf]
+ noPrint $ timeout_ (xstPath sim) ["-ifn", toTextIgnore xstFile]
+ noPrint $ run_ (netgenPath sim)
+ ["-w", "-ofmt", "verilog", toTextIgnore $ modFile <.> "ngc", toTextIgnore outf]
+ noPrint $ run_ "sed" ["-i", "/^`ifndef/,/^`endif/ d; s/ *Timestamp: .*//;", toTextIgnore outf]
where
modFile = fromText $ modName m
xstFile = modFile <.> "xst"
diff --git a/src/VeriFuzz/Simulator/Yosys.hs b/src/VeriFuzz/Simulator/Yosys.hs
index 286a132..c63d549 100644
--- a/src/VeriFuzz/Simulator/Yosys.hs
+++ b/src/VeriFuzz/Simulator/Yosys.hs
@@ -47,7 +47,7 @@ writeSimFile _ m file = do
runSynthYosys :: Yosys -> ModDecl -> FilePath -> Sh ()
runSynthYosys sim m outf = do
writefile inpf $ genSource m
- run_ (yosysPath sim) ["-q", "-b", "verilog -noattr", "-o", out, "-S", inp]
+ noPrint $ run_ (yosysPath sim) ["-q", "-b", "verilog -noattr", "-o", out, "-S", inp]
where
inpf = "rtl.v"
inp = toTextIgnore inpf
@@ -64,7 +64,7 @@ runEquivYosys yosys sim1 sim2 m = do
writefile checkFile $ yosysSatConfig sim1 sim2 m
runSynth sim1 m $ fromText [st|syn_#{toText sim1}.v|]
runMaybeSynth sim2 m
- run_ (yosysPath yosys) [toTextIgnore checkFile]
+ noPrint $ run_ (yosysPath yosys) [toTextIgnore checkFile]
where
checkFile = fromText [st|test.#{toText sim1}.#{maybe "rtl" toText sim2}.ys|]
@@ -75,4 +75,4 @@ runEquiv yosys sim1 sim2 m = do
writefile "test.sby" $ sbyConfig root sim1 sim2 m
runSynth sim1 m $ fromText [st|syn_#{toText sim1}.v|]
runMaybeSynth sim2 m
- run_ "sby" ["test.sby"]
+ noPrint $ run_ "sby" ["test.sby"]