aboutsummaryrefslogtreecommitdiffstats
path: root/app/Main.hs
blob: 1249c41a86c9b1fc0e92f5815aed7349e39e4d4b (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
module Main where

import           Control.Concurrent
import           Data.Text           (Text)
import qualified Data.Text           as T
import           Options.Applicative
import qualified Shelly              as S
import qualified Test.QuickCheck     as QC
import qualified VeriFuzz            as V

data Tool = Yosys
          | XST
          | Icarus

instance Show Tool where
  show Yosys  = "yosys"
  show XST    = "xst"
  show Icarus = "icarus"

data Opts = Fuzz { fuzzOutput :: Text
                 }
          | Rerun { tool :: Tool
                  }
          | Generate { fileName :: S.FilePath
                     }
          | Parse { fileName :: S.FilePath
                  }

myForkIO :: IO () -> IO (MVar ())
myForkIO io = do
  mvar <- newEmptyMVar
  _ <- forkFinally io (\_ -> putMVar mvar ())
  return mvar

textOption :: Mod OptionFields String -> Parser Text
textOption = fmap T.pack . strOption

optReader :: (String -> Maybe a) -> ReadM a
optReader f = eitherReader $ \arg ->
  case f arg of
    Just a  -> Right a
    Nothing -> Left $ "Cannot parse option: " <> arg

parseSynth :: String -> Maybe Tool
parseSynth val
  | val == "yosys" = Just Yosys
  | val == "xst"= Just XST
  | otherwise = Nothing

parseSim :: String -> Maybe Tool
parseSim val
  | val == "icarus" = Just Icarus
  | otherwise = Nothing

fuzzOpts :: Parser Opts
fuzzOpts = Fuzz
  <$> textOption
  ( long "output"
    <> short 'o'
    <> metavar "DIR"
    <> help "Output directory that the fuzz run takes place in."
    <> showDefault
    <> value "output"
  )

rerunOpts :: Parser Opts
rerunOpts = Rerun
  <$> ( option (optReader parseSynth)
        ( long "synth"
          <> metavar "SYNTH"
          <> help "Rerun using a synthesiser (yosys|xst)."
          <> showDefault
          <> value Yosys
        )
        <|> option (optReader parseSim)
        ( long "sim"
          <> metavar "SIM"
          <> help "Rerun using a simulator (icarus)."
          <> showDefault
          <> value Icarus
        )
      )

genOpts :: Parser Opts
genOpts = Generate . S.fromText <$> textOption
  ( long "output"
    <> short 'o'
    <> metavar "FILE"
    <> help "Verilog output file."
    <> showDefault
    <> value "main.v"
  )

parseOpts :: Parser Opts
parseOpts = Parse . S.fromText . T.pack <$> strArgument
  ( metavar "FILE"
    <> help "Verilog input file."
  )

argparse :: Parser Opts
argparse =
  hsubparser (command "fuzz"
              (info fuzzOpts
               (progDesc "Run fuzzing on the specified simulators and synthesisers."))
              <> metavar "fuzz")
  <|> hsubparser (command "rerun"
                  (info rerunOpts
                   (progDesc "Rerun a Verilog file with a simulator or a synthesiser."))
                  <> metavar "rerun")
  <|> hsubparser (command "generate"
                  (info genOpts
                   (progDesc "Generate a random Verilog program."))
                  <> metavar "generate")
  <|> hsubparser (command "parse"
                  (info parseOpts
                   (progDesc "Parse a verilog file and output a pretty printed version."))
                  <> metavar "parse")

opts :: ParserInfo Opts
opts = info (argparse <**> helper)
       ( fullDesc
         <> progDesc "Fuzz different simulators and synthesisers."
         <> header "VeriFuzz - A hardware simulator and synthesiser Verilog fuzzer." )

handleOpts :: Opts -> IO ()
handleOpts (Fuzz _) = do
  num <- getNumCapabilities
  vars <- sequence $ (\x -> myForkIO $
                       V.runEquivalence (V.randomMod 10 100)
                       ("test_" <> T.pack (show x)) 0) <$> [1..num]
  sequence_ $ takeMVar <$> vars
handleOpts (Generate f) = do
  g <- QC.generate $ V.randomMod 50 1000
  S.shelly . S.writefile f $ V.genSource g
handleOpts (Parse f) = do
  verilogSrc <- readFile file
  case V.parseVerilog file verilogSrc of
    Left l  -> print l
    Right v -> print $ V.GenVerilog v
  where
    file = T.unpack . S.toTextIgnore $ f
handleOpts (Rerun _) = undefined

main :: IO ()
 --main = sample (arbitrary :: Gen (Circuit Input))
main = do
  optsparsed <- execParser opts
  handleOpts optsparsed