aboutsummaryrefslogtreecommitdiffstats
path: root/src/VeriFuzz/Sim/Icarus.hs
blob: 9041d1437bacffe99ce2c37e582e3f98bd229d54 (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
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
{-|
Module      : VeriFuzz.Sim.Icarus
Description : Icarus verilog module.
Copyright   : (c) 2018-2019, Yann Herklotz
License     : BSD-3
Maintainer  : yann [at] yannherklotz [dot] com
Stability   : experimental
Portability : POSIX

Icarus verilog module.
-}

module VeriFuzz.Sim.Icarus
    ( Icarus(..)
    , defaultIcarus
    , runSimIc
    )
where

import           Control.DeepSeq           (NFData, rnf, rwhnf)
import           Control.Lens
import           Control.Monad             (void)
import           Crypto.Hash               (Digest, hash)
import           Crypto.Hash.Algorithms    (SHA256)
import           Data.Binary               (encode)
import           Data.Bits
import qualified Data.ByteArray            as BA (convert)
import           Data.ByteString           (ByteString)
import qualified Data.ByteString           as B
import           Data.ByteString.Lazy      (toStrict)
import qualified Data.ByteString.Lazy      as L (ByteString)
import           Data.Char                 (digitToInt)
import           Data.Foldable             (fold)
import           Data.List                 (transpose)
import           Data.Maybe                (listToMaybe)
import           Data.Text                 (Text)
import qualified Data.Text                 as T
import           Numeric                   (readInt)
import           Prelude                   hiding (FilePath)
import           Shelly
import           Shelly.Lifted             (liftSh)
import           VeriFuzz.Sim.Internal
import           VeriFuzz.Sim.Template
import           VeriFuzz.Verilog.AST
import           VeriFuzz.Verilog.BitVec
import           VeriFuzz.Verilog.CodeGen
import           VeriFuzz.Verilog.Internal
import           VeriFuzz.Verilog.Mutate

data Icarus = Icarus { icarusPath :: FilePath
                     , vvpPath    :: FilePath
                     }
              deriving (Eq)

instance Show Icarus where
    show _ = "iverilog"

instance Tool Icarus where
  toText _ = "iverilog"

instance Simulator Icarus where
  runSim = runSimIcarus
  runSimWithFile = runSimIcarusWithFile

instance NFData Icarus where
    rnf = rwhnf

defaultIcarus :: Icarus
defaultIcarus = Icarus "iverilog" "vvp"

addDisplay :: [Statement] -> [Statement]
addDisplay s = concat $ transpose
    [ s
    , replicate l $ TimeCtrl 1 Nothing
    , replicate l . SysTaskEnable $ Task "display" ["%b", Id "y"]
    ]
    where l = length s

assignFunc :: [Port] -> ByteString -> Statement
assignFunc inp bs =
    NonBlockAssign
        . Assign conc Nothing
        . Number
        . BitVec (B.length bs * 8)
        $ bsToI bs
    where conc = RegConcat (portToExpr <$> inp)

convert :: Text -> ByteString
convert =
    toStrict
        . (encode :: Integer -> L.ByteString)
        . maybe 0 fst
        . listToMaybe
        . readInt 2 (`elem` ("01" :: String)) digitToInt
        . T.unpack

mask :: Text -> Text
mask = T.replace "x" "0"

callback :: ByteString -> Text -> ByteString
callback b t = b <> convert (mask t)

runSimIcarus :: Icarus -> SourceInfo -> [ByteString] -> ResultSh ByteString
runSimIcarus sim rinfo bss = do
    let tb = ModDecl
            "main"
            []
            []
            [ Initial
              $  fold (addDisplay $ assignFunc (_modInPorts m) <$> bss)
              <> (SysTaskEnable $ Task "finish" [])
            ]
            []
    let newtb     = instantiateMod m tb
    let modWithTb = Verilog [newtb, m]
    liftSh . writefile "main.v" $ genSource modWithTb
    annotate SimFail $ runSimWithFile sim "main.v" bss
    where m = rinfo ^. mainModule

runSimIcarusWithFile
    :: Icarus -> FilePath -> [ByteString] -> ResultSh ByteString
runSimIcarusWithFile sim f _ = annotate SimFail . liftSh $ do
    dir <- pwd
    logCommand_ dir "icarus"
        $ run (icarusPath sim) ["-o", "main", toTextIgnore f]
    B.take 8 . BA.convert . (hash :: ByteString -> Digest SHA256) <$> logCommand
        dir
        "vvp"
        (runFoldLines (mempty :: ByteString) callback (vvpPath sim) ["main"])

fromBytes :: ByteString -> Integer
fromBytes = B.foldl' f 0 where f a b = a `shiftL` 8 .|. fromIntegral b

runSimIc
    :: (Synthesiser b)
    => Icarus
    -> b
    -> SourceInfo
    -> [ByteString]
    -> ResultSh ByteString
runSimIc sim1 synth1 srcInfo bss = do
    dir <- liftSh pwd
    let top      = srcInfo ^. mainModule
    let inConcat = (RegConcat (Id . _portName <$> (top ^. modInPorts)))
    let
        tb = instantiateMod top $ ModDecl
            "testbench"
            []
            []
            [ Initial
            $  fold
                   [ BlockAssign (Assign "clk" Nothing 0)
                   , BlockAssign (Assign inConcat Nothing 0)
                   ]
            <> fold
                   (   (\r -> TimeCtrl
                           10
                           (Just $ BlockAssign (Assign inConcat Nothing r))
                       )
                   .   fromInteger
                   .   fromBytes
                   <$> bss
                   )
            <> (SysTaskEnable $ Task "finish" [])
            , Always . TimeCtrl 5 . Just $ BlockAssign
                (Assign "clk" Nothing (UnOp UnNot (Id "clk")))
            , Always . EventCtrl (EPosEdge "clk") . Just . SysTaskEnable $ Task
                "strobe"
                ["%b", Id "y"]
            ]
            []

    liftSh . writefile "testbench.v" $ icarusTestbench (Verilog [tb]) synth1
    liftSh $ exe dir "icarus" "iverilog" ["-o", "main", "testbench.v"]
    liftSh
        $   B.take 8
        .   BA.convert
        .   (hash :: ByteString -> Digest SHA256)
        <$> logCommand
                dir
                "vvp"
                (runFoldLines (mempty :: ByteString)
                              callback
                              (vvpPath sim1)
                              ["main"]
                )
  where
    exe dir name e = void . errExit False . logCommand dir name . timeout e