aboutsummaryrefslogtreecommitdiffstats
path: root/src/Verismith/Tool/XST.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Verismith/Tool/XST.hs')
-rw-r--r--src/Verismith/Tool/XST.hs85
1 files changed, 85 insertions, 0 deletions
diff --git a/src/Verismith/Tool/XST.hs b/src/Verismith/Tool/XST.hs
new file mode 100644
index 0000000..c713e0b
--- /dev/null
+++ b/src/Verismith/Tool/XST.hs
@@ -0,0 +1,85 @@
+{-|
+Module : Verismith.Tool.XST
+Description : XST (ise) simulator implementation.
+Copyright : (c) 2018-2019, Yann Herklotz
+License : BSD-3
+Maintainer : yann [at] yannherklotz [dot] com
+Stability : experimental
+Portability : POSIX
+
+XST (ise) simulator implementation.
+-}
+
+{-# LANGUAGE QuasiQuotes #-}
+
+module Verismith.Tool.XST
+ ( XST(..)
+ , defaultXST
+ )
+where
+
+import Control.DeepSeq (NFData, rnf, rwhnf)
+import Data.Text (Text, unpack)
+import Prelude hiding (FilePath)
+import Shelly
+import Shelly.Lifted (liftSh)
+import Text.Shakespeare.Text (st)
+import Verismith.Tool.Internal
+import Verismith.Tool.Template
+import Verismith.Verilog.AST
+import Verismith.Verilog.CodeGen
+
+data XST = XST { xstBin :: !(Maybe FilePath)
+ , xstDesc :: {-# UNPACK #-} !Text
+ , xstOutput :: {-# UNPACK #-} !FilePath
+ }
+ deriving (Eq)
+
+instance Tool XST where
+ toText (XST _ t _) = t
+
+instance Show XST where
+ show t = unpack $ toText t
+
+instance Synthesiser XST where
+ runSynth = runSynthXST
+ synthOutput = xstOutput
+ setSynthOutput (XST a b _) = XST a b
+
+instance NFData XST where
+ rnf = rwhnf
+
+defaultXST :: XST
+defaultXST = XST Nothing "xst" "syn_xst.v"
+
+runSynthXST :: XST -> SourceInfo -> ResultSh ()
+runSynthXST sim (SourceInfo top src) = do
+ dir <- liftSh pwd
+ let exec n = execute_
+ SynthFail
+ dir
+ "xst"
+ (maybe (fromText n) (</> fromText n) $ xstBin sim)
+ liftSh $ do
+ writefile xstFile $ xstSynthConfig top
+ writefile prjFile [st|verilog work "rtl.v"|]
+ writefile "rtl.v" $ genSource src
+ exec "xst" ["-ifn", toTextIgnore xstFile]
+ exec
+ "netgen"
+ [ "-w"
+ , "-ofmt"
+ , "verilog"
+ , toTextIgnore $ modFile <.> "ngc"
+ , toTextIgnore $ synthOutput sim
+ ]
+ liftSh . noPrint $ run_
+ "sed"
+ [ "-i"
+ , "/^`ifndef/,/^`endif/ d; s/ *Timestamp: .*//;"
+ , toTextIgnore $ synthOutput sim
+ ]
+ where
+ modFile = fromText top
+ xstFile = modFile <.> "xst"
+ prjFile = modFile <.> "prj"