aboutsummaryrefslogtreecommitdiffstats
path: root/src/VeriFuzz/Simulator
diff options
context:
space:
mode:
authorYann Herklotz <ymherklotz@gmail.com>2019-02-01 19:39:52 +0000
committerYann Herklotz <ymherklotz@gmail.com>2019-02-01 19:39:52 +0000
commit1067284cc1f6ca8ba646545c5b8d0a79cc2e41ad (patch)
tree2c9a8d54bf6f9870f0ae62c150803ccec90d46e7 /src/VeriFuzz/Simulator
parenta38289ca9d96e97bc4e65b67c50f5805d56a3d86 (diff)
downloadverismith-1067284cc1f6ca8ba646545c5b8d0a79cc2e41ad.tar.gz
verismith-1067284cc1f6ca8ba646545c5b8d0a79cc2e41ad.zip
More restructuring
Diffstat (limited to 'src/VeriFuzz/Simulator')
-rw-r--r--src/VeriFuzz/Simulator/General.hs70
-rw-r--r--src/VeriFuzz/Simulator/Icarus.hs63
-rw-r--r--src/VeriFuzz/Simulator/Xst.hs57
-rw-r--r--src/VeriFuzz/Simulator/Yosys.hs81
4 files changed, 0 insertions, 271 deletions
diff --git a/src/VeriFuzz/Simulator/General.hs b/src/VeriFuzz/Simulator/General.hs
deleted file mode 100644
index dbd1da0..0000000
--- a/src/VeriFuzz/Simulator/General.hs
+++ /dev/null
@@ -1,70 +0,0 @@
-{-|
-Module : VeriFuzz.Simulator.General
-Description : Class of the simulator.
-Copyright : (c) 2018-2019, Yann Herklotz Grave
-License : BSD-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Portability : POSIX
-
-Class of the simulator and the synthesize tool.
--}
-
-module VeriFuzz.Simulator.General where
-
-import Data.Bits (shiftL)
-import Data.ByteString (ByteString)
-import qualified Data.ByteString as B
-import Data.Text (Text)
-import qualified Data.Text as T
-import Prelude hiding (FilePath)
-import Shelly
-import System.FilePath.Posix (takeBaseName)
-import VeriFuzz.Verilog.AST
-
--- | Simulator class.
-class Simulator a where
- toText :: a -> Text
-
--- | Simulation type class.
-class (Simulator a) => Simulate a where
- runSim :: a -- ^ Simulator instance
- -> ModDecl -- ^ Module to simulate
- -> [ByteString] -- ^ Inputs to simulate
- -> Sh Int -- ^ Returns the value of the hash at the output of the testbench.
-
--- | Synthesize type class.
-class (Simulator a) => Synthesize a where
- runSynth :: a -- ^ Synthesize tool instance
- -> ModDecl -- ^ Module to synthesize
- -> FilePath -- ^ Output verilog file for the module
- -> Sh () -- ^ does not return any values
-
-rootPath :: Sh FilePath
-rootPath = do
- current <- pwd
- maybe current fromText <$> get_env "VERIFUZZ_ROOT"
-
-timeout :: FilePath -> [Text] -> Sh Text
-timeout = command1 "timeout" ["180"] . toTextIgnore
-{-# INLINE timeout #-}
-
-timeout_ :: FilePath -> [Text] -> Sh ()
-timeout_ = command1_ "timeout" ["180"] . toTextIgnore
-{-# INLINE timeout_ #-}
-
--- | Helper function to convert bytestrings to integers
-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
-
-echoP :: Text -> Sh ()
-echoP t = do
- fn <- pwd
- echo $ bname fn <> " :: " <> t
- where
- bname = T.pack . takeBaseName . T.unpack . toTextIgnore
diff --git a/src/VeriFuzz/Simulator/Icarus.hs b/src/VeriFuzz/Simulator/Icarus.hs
deleted file mode 100644
index 527322a..0000000
--- a/src/VeriFuzz/Simulator/Icarus.hs
+++ /dev/null
@@ -1,63 +0,0 @@
-{-|
-Module : VeriFuzz.Simulator.Icarus
-Description : Icarus verilog module.
-Copyright : (c) 2018-2019, Yann Herklotz Grave
-License : BSD-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Portability : POSIX
-
-Icarus verilog module.
--}
-
-module VeriFuzz.Simulator.Icarus where
-
-import Control.Lens
-import Data.ByteString (ByteString)
-import qualified Data.ByteString as B
-import Data.Foldable (fold)
-import Data.Hashable
-import Data.List (transpose)
-import Prelude hiding (FilePath)
-import Shelly
-import VeriFuzz.Simulator.General
-import VeriFuzz.Verilog
-
-data Icarus = Icarus { icarusPath :: FilePath
- , vvpPath :: FilePath
- }
-
-instance Simulator Icarus where
- toText _ = "iverilog"
-
-instance Simulate Icarus where
- runSim = runSimIcarus
-
-defaultIcarus :: Icarus
-defaultIcarus = Icarus "iverilog" "vvp"
-
-addDisplay :: [Stmnt] -> [Stmnt]
-addDisplay s = concat $ transpose
- [s, replicate l $ TimeCtrl 1 Nothing, replicate l . SysTaskEnable $ Task "display" ["%h", Id "y"]]
- where l = length s
-
-assignFunc :: [Port] -> ByteString -> Stmnt
-assignFunc inp bs = NonBlockAssign . Assign conc Nothing . Number (B.length bs * 4) $ bsToI bs
- where conc = RegConcat (portToExpr <$> inp)
-
-runSimIcarus :: Icarus -> ModDecl -> [ByteString] -> Sh Int
-runSimIcarus sim m bss = do
- let tb = ModDecl
- "main"
- []
- []
- [ Initial
- $ fold (addDisplay $ assignFunc (m ^. modInPorts) <$> bss)
- <> (SysTaskEnable $ Task "finish" [])
- ]
- let newtb = instantiateMod m tb
- let modWithTb = VerilogSrc $ Description <$> [newtb, m]
- writefile "main.v" $ genSource modWithTb
- echoP "Run icarus"
- 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
deleted file mode 100644
index 52272c3..0000000
--- a/src/VeriFuzz/Simulator/Xst.hs
+++ /dev/null
@@ -1,57 +0,0 @@
-{-|
-Module : VeriFuzz.Simulator.Xst
-Description : Xst (ise) simulator implementation.
-Copyright : (c) 2018-2019, Yann Herklotz Grave
-License : BSD-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Portability : POSIX
-
-Xst (ise) simulator implementation.
--}
-
-{-# LANGUAGE QuasiQuotes #-}
-
-module VeriFuzz.Simulator.Xst where
-
-import Control.Lens hiding ((<.>))
-import qualified Data.Text as T
-import Prelude hiding (FilePath)
-import Shelly
-import System.FilePath.Posix (takeBaseName)
-import Text.Shakespeare.Text (st)
-import VeriFuzz.Simulator.General
-import VeriFuzz.Simulator.Internal.Template
-import VeriFuzz.Verilog
-import VeriFuzz.Verilog
-
-data Xst = Xst { xstPath :: FilePath
- , netgenPath :: FilePath
- }
-
-instance Simulator Xst where
- toText _ = "xst"
-
-instance Synthesize Xst where
- runSynth = runSynthXst
-
-defaultXst :: Xst
-defaultXst =
- Xst "/opt/Xilinx/14.7/ISE_DS/ISE/bin/lin64/xst" "/opt/Xilinx/14.7/ISE_DS/ISE/bin/lin64/netgen"
-
-runSynthXst :: Xst -> ModDecl -> FilePath -> Sh ()
-runSynthXst sim m outf = do
- writefile xstFile $ xstSynthConfig m
- writefile prjFile [st|verilog work "rtl.v"|]
- writefile "rtl.v" $ genSource m
- echoP "Run xst"
- noPrint $ timeout_ (xstPath sim) ["-ifn", toTextIgnore xstFile]
- echoP "Run netgen"
- noPrint $ run_ (netgenPath sim)
- ["-w", "-ofmt", "verilog", toTextIgnore $ modFile <.> "ngc", toTextIgnore outf]
- echoP "Clean synthesized file"
- noPrint $ run_ "sed" ["-i", "/^`ifndef/,/^`endif/ d; s/ *Timestamp: .*//;", toTextIgnore outf]
- where
- modFile = fromText $ modName m
- xstFile = modFile <.> "xst"
- prjFile = modFile <.> "prj"
diff --git a/src/VeriFuzz/Simulator/Yosys.hs b/src/VeriFuzz/Simulator/Yosys.hs
deleted file mode 100644
index e18de5a..0000000
--- a/src/VeriFuzz/Simulator/Yosys.hs
+++ /dev/null
@@ -1,81 +0,0 @@
-{-|
-Module : VeriFuzz.Simulator.Yosys
-Description : Yosys simulator implementation.
-Copyright : (c) 2018-2019, Yann Herklotz Grave
-License : BSD-3
-Maintainer : ymherklotz [at] gmail [dot] com
-Stability : experimental
-Portability : POSIX
-
-Yosys simulator implementation.
--}
-
-{-# LANGUAGE QuasiQuotes #-}
-
-module VeriFuzz.Simulator.Yosys where
-
-import Data.Maybe (fromMaybe)
-import Data.Text (Text)
-import qualified Data.Text as T
-import Prelude hiding (FilePath)
-import Shelly
-import Text.Shakespeare.Text (st)
-import VeriFuzz.Simulator.General
-import VeriFuzz.Simulator.Internal.Template
-import VeriFuzz.Verilog
-
-newtype Yosys = Yosys { yosysPath :: FilePath }
-
-instance Simulator Yosys where
- toText _ = "yosys"
-
-instance Synthesize Yosys where
- runSynth = runSynthYosys
-
-defaultYosys :: Yosys
-defaultYosys = Yosys "/usr/bin/yosys"
-
-writeSimFile
- :: Yosys -- ^ Simulator instance
- -> ModDecl -- ^ Current module
- -> FilePath -- ^ Output sim file
- -> Sh ()
-writeSimFile _ m file = do
- writefile "rtl.v" $ genSource m
- writefile file yosysSimConfig
-
-runSynthYosys :: Yosys -> ModDecl -> FilePath -> Sh ()
-runSynthYosys sim m outf = do
- writefile inpf $ genSource m
- echoP "Run yosim"
- noPrint $ run_ (yosysPath sim) ["-q", "-b", "verilog -noattr", "-o", out, "-S", inp]
- where
- inpf = "rtl.v"
- inp = toTextIgnore inpf
- out = toTextIgnore outf
- -- ids = T.intercalate "," $ allVars m ^.. traverse . getIdentifier
-
-runMaybeSynth :: (Synthesize a) => Maybe a -> ModDecl -> Sh ()
-runMaybeSynth (Just sim) m = runSynth sim m $ fromText [st|syn_#{toText sim}.v|]
-runMaybeSynth Nothing m = writefile "syn_rtl.v" $ genSource m
-
-runEquivYosys :: (Synthesize a, Synthesize b) => Yosys -> a -> Maybe b -> ModDecl -> Sh ()
-runEquivYosys yosys sim1 sim2 m = do
- writefile "top.v" . genSource . initMod $ makeTop 2 m
- writefile checkFile $ yosysSatConfig sim1 sim2 m
- runSynth sim1 m $ fromText [st|syn_#{toText sim1}.v|]
- runMaybeSynth sim2 m
- echoP "Run yosys"
- noPrint $ run_ (yosysPath yosys) [toTextIgnore checkFile]
- where
- checkFile = fromText [st|test.#{toText sim1}.#{maybe "rtl" toText sim2}.ys|]
-
-runEquiv :: (Synthesize a, Synthesize b) => Yosys -> a -> Maybe b -> ModDecl -> Sh ()
-runEquiv yosys sim1 sim2 m = do
- root <- rootPath
- writefile "top.v" . genSource . initMod $ makeTopAssert m
- writefile "test.sby" $ sbyConfig root sim1 sim2 m
- runSynth sim1 m $ fromText [st|syn_#{toText sim1}.v|]
- runMaybeSynth sim2 m
- echoP "Run SymbiYosys"
- noPrint $ run_ "sby" ["test.sby"]