aboutsummaryrefslogtreecommitdiffstats
path: root/src/Verismith/Tool/XST.hs
blob: c713e0b79f12007a44e508a318953f4b1d194a44 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
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"