aboutsummaryrefslogtreecommitdiffstats
path: root/src/VeriFuzz/Simulator/Xst.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/VeriFuzz/Simulator/Xst.hs')
-rw-r--r--src/VeriFuzz/Simulator/Xst.hs58
1 files changed, 58 insertions, 0 deletions
diff --git a/src/VeriFuzz/Simulator/Xst.hs b/src/VeriFuzz/Simulator/Xst.hs
new file mode 100644
index 0000000..902b244
--- /dev/null
+++ b/src/VeriFuzz/Simulator/Xst.hs
@@ -0,0 +1,58 @@
+{-|
+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 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.Verilog.AST
+import VeriFuzz.Verilog.CodeGen
+
+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 mod outf = do
+ writefile xstFile [st|run
+-ifn #{modName}.prj -ofn #{modName} -p artix7 -top #{modName}
+-iobuf NO -ram_extract NO -rom_extract NO -use_dsp48 NO
+-fsm_extract YES -fsm_encoding Auto
+-change_error_to_warning "HDLCompiler:226 HDLCompiler:1832"
+|]
+ writefile prjFile [st|verilog work "rtl.v"|]
+ writefile "rtl.v" $ genSource mod
+ 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]
+ where
+ modName = mod ^. moduleId . getIdentifier
+ modFile = fromText modName
+ xstFile = modFile <.> "xst"
+ prjFile = modFile <.> "prj"
+ vFile = modFile <.> "v"