aboutsummaryrefslogtreecommitdiffstats
path: root/src/Verismith/Report.hs
blob: 6c0d537e65b249bb1472c54bae2572f7c218d9c0 (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
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}

-- |
-- Module      : Verismith.Report
-- Description : Generate a report from a fuzz run.
-- Copyright   : (c) 2019, Yann Herklotz Grave
-- License     : GPL-3
-- Maintainer  : yann [at] yannherklotz [dot] com
-- Stability   : experimental
-- Portability : POSIX
--
-- Generate a report from a fuzz run.
module Verismith.Report
  ( SynthTool (..),
    SynthStatus (..),
    SynthResult (..),
    SimResult (..),
    SimTool (..),
    FuzzReport (..),
    printResultReport,
    printSummary,
    synthResults,
    simResults,
    synthStatus,
    equivTime,
    fuzzDir,
    fileLines,
    reducTime,
    synthTime,
    defaultIcarusSim,
    defaultVivadoSynth,
    defaultYosysSynth,
    defaultXSTSynth,
    defaultQuartusSynth,
    defaultQuartusLightSynth,
    defaultIdentitySynth,
    descriptionToSim,
    descriptionToSynth,
  )
where

import Control.DeepSeq (NFData, rnf)
import Control.Lens hiding ((<.>), Identity)
import Data.Bifunctor (bimap)
import Data.ByteString (ByteString)
import Data.Maybe (fromMaybe)
import Data.Monoid (Endo)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.Lazy (toStrict)
import Data.Time
import Shelly
  ( (<.>),
    (</>),
    FilePath,
    fromText,
    toTextIgnore,
  )
import Text.Blaze.Html ((!), Html)
import Text.Blaze.Html.Renderer.Text (renderHtml)
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as A
import Verismith.Config
import Verismith.Internal
import Verismith.Result
import Verismith.Tool
import Verismith.Tool.Internal
import Prelude hiding (FilePath)

-- | Common type alias for synthesis results
type UResult = Result Failed ()

-- | Commont type alias for simulation results
type BResult = Result Failed ByteString

data SynthTool
  = XSTSynth {-# UNPACK #-} !XST
  | VivadoSynth {-# UNPACK #-} !Vivado
  | YosysSynth {-# UNPACK #-} !Yosys
  | QuartusSynth {-# UNPACK #-} !Quartus
  | QuartusLightSynth {-# UNPACK #-} !QuartusLight
  | IdentitySynth {-# UNPACK #-} !Identity
  deriving (Eq)

instance NFData SynthTool where
  rnf (XSTSynth a) = rnf a
  rnf (VivadoSynth a) = rnf a
  rnf (YosysSynth a) = rnf a
  rnf (QuartusSynth a) = rnf a
  rnf (QuartusLightSynth a) = rnf a
  rnf (IdentitySynth a) = rnf a

instance Show SynthTool where
  show (XSTSynth xst) = show xst
  show (VivadoSynth vivado) = show vivado
  show (YosysSynth yosys) = show yosys
  show (QuartusSynth quartus) = show quartus
  show (QuartusLightSynth quartus) = show quartus
  show (IdentitySynth identity) = show identity

instance Tool SynthTool where
  toText (XSTSynth xst) = toText xst
  toText (VivadoSynth vivado) = toText vivado
  toText (YosysSynth yosys) = toText yosys
  toText (QuartusSynth quartus) = toText quartus
  toText (QuartusLightSynth quartus) = toText quartus
  toText (IdentitySynth identity) = toText identity

instance Synthesiser SynthTool where
  runSynth (XSTSynth xst) = runSynth xst
  runSynth (VivadoSynth vivado) = runSynth vivado
  runSynth (YosysSynth yosys) = runSynth yosys
  runSynth (QuartusSynth quartus) = runSynth quartus
  runSynth (QuartusLightSynth quartus) = runSynth quartus
  runSynth (IdentitySynth identity) = runSynth identity

  synthOutput (XSTSynth xst) = synthOutput xst
  synthOutput (VivadoSynth vivado) = synthOutput vivado
  synthOutput (YosysSynth yosys) = synthOutput yosys
  synthOutput (QuartusSynth quartus) = synthOutput quartus
  synthOutput (QuartusLightSynth quartus) = synthOutput quartus
  synthOutput (IdentitySynth identity) = synthOutput identity

  setSynthOutput (YosysSynth yosys) = YosysSynth . setSynthOutput yosys
  setSynthOutput (XSTSynth xst) = XSTSynth . setSynthOutput xst
  setSynthOutput (VivadoSynth vivado) = VivadoSynth . setSynthOutput vivado
  setSynthOutput (QuartusSynth quartus) = QuartusSynth . setSynthOutput quartus
  setSynthOutput (QuartusLightSynth quartus) = QuartusLightSynth . setSynthOutput quartus
  setSynthOutput (IdentitySynth identity) = IdentitySynth . setSynthOutput identity

defaultYosysSynth :: SynthTool
defaultYosysSynth = YosysSynth defaultYosys

defaultQuartusSynth :: SynthTool
defaultQuartusSynth = QuartusSynth defaultQuartus

defaultQuartusLightSynth :: SynthTool
defaultQuartusLightSynth = QuartusLightSynth defaultQuartusLight

defaultVivadoSynth :: SynthTool
defaultVivadoSynth = VivadoSynth defaultVivado

defaultXSTSynth :: SynthTool
defaultXSTSynth = XSTSynth defaultXST

defaultIdentitySynth :: SynthTool
defaultIdentitySynth = IdentitySynth defaultIdentity

newtype SimTool = IcarusSim Icarus
  deriving (Eq)

instance NFData SimTool where
  rnf (IcarusSim a) = rnf a

instance Tool SimTool where
  toText (IcarusSim icarus) = toText icarus

instance Simulator SimTool where
  runSim (IcarusSim icarus) = runSim icarus
  runSimWithFile (IcarusSim icarus) = runSimWithFile icarus

instance Show SimTool where
  show (IcarusSim icarus) = show icarus

defaultIcarusSim :: SimTool
defaultIcarusSim = IcarusSim defaultIcarus

-- | The results from running a tool through a simulator. It can either fail or
-- return a result, which is most likely a 'ByteString'.
data SimResult = SimResult !SynthTool !SimTool ![ByteString] !BResult !NominalDiffTime
  deriving (Eq)

instance Show SimResult where
  show (SimResult synth sim _ r d) = show synth <> ", " <> show sim <> ": " <> show (bimap show (T.unpack . showBS) r) <> " (" <> show d <> ")"

getSimResult :: SimResult -> UResult
getSimResult (SimResult _ _ _ (Pass _) _) = Pass ()
getSimResult (SimResult _ _ _ (Fail b) _) = Fail b

-- | The results of comparing the synthesised outputs of two files using a
-- formal equivalence checker. This will either return a failure or an output
-- which is most likely '()'.
data SynthResult = SynthResult !SynthTool !SynthTool !UResult !NominalDiffTime
  deriving (Eq)

instance Show SynthResult where
  show (SynthResult synth synth2 r d) = show synth <> ", " <> show synth2 <> ": " <> show r <> " (" <> show d <> ")"

getSynthResult :: SynthResult -> UResult
getSynthResult (SynthResult _ _ a _) = a

-- | The status of the synthesis using a simulator. This will be checked before
-- attempting to run the equivalence checks on the simulator, as that would be
-- unnecessary otherwise.
data SynthStatus = SynthStatus !SynthTool !UResult !NominalDiffTime
  deriving (Eq)

getSynthStatus :: SynthStatus -> UResult
getSynthStatus (SynthStatus _ a _) = a

instance Show SynthStatus where
  show (SynthStatus synth r d) = "synthesis " <> show synth <> ": " <> show r <> " (" <> show d <> ")"

-- | The complete state that will be used during fuzzing, which contains the
-- results from all the operations.
data FuzzReport
  = FuzzReport
      { _fuzzDir :: !FilePath,
        -- | Results of the equivalence check.
        _synthResults :: ![SynthResult],
        -- | Results of the simulation.
        _simResults :: ![SimResult],
        -- | Results of the synthesis step.
        _synthStatus :: ![SynthStatus],
        _fileLines :: {-# UNPACK #-} !Int,
        _synthTime :: !NominalDiffTime,
        _equivTime :: !NominalDiffTime,
        _reducTime :: !NominalDiffTime
      }
  deriving (Eq, Show)

$(makeLenses ''FuzzReport)

descriptionToSim :: SimDescription -> SimTool
descriptionToSim (SimDescription "icarus") = defaultIcarusSim
descriptionToSim s =
  error $ "Could not find implementation for simulator '" <> show s <> "'"

-- | Convert a description to a synthesiser.
descriptionToSynth :: SynthDescription -> SynthTool
descriptionToSynth (SynthDescription "yosys" bin desc out) =
  YosysSynth
    . Yosys (fromText <$> bin) (fromMaybe (yosysDesc defaultYosys) desc)
    $ maybe (yosysOutput defaultYosys) fromText out
descriptionToSynth (SynthDescription "vivado" bin desc out) =
  VivadoSynth
    . Vivado (fromText <$> bin) (fromMaybe (vivadoDesc defaultVivado) desc)
    $ maybe (vivadoOutput defaultVivado) fromText out
descriptionToSynth (SynthDescription "xst" bin desc out) =
  XSTSynth
    . XST (fromText <$> bin) (fromMaybe (xstDesc defaultXST) desc)
    $ maybe (xstOutput defaultXST) fromText out
descriptionToSynth (SynthDescription "quartus" bin desc out) =
  QuartusSynth
    . Quartus
      (fromText <$> bin)
      (fromMaybe (quartusDesc defaultQuartus) desc)
    $ maybe (quartusOutput defaultQuartus) fromText out
descriptionToSynth (SynthDescription "quartuslight" bin desc out) =
  QuartusLightSynth
    . QuartusLight
      (fromText <$> bin)
      (fromMaybe (quartusDesc defaultQuartus) desc)
    $ maybe (quartusOutput defaultQuartus) fromText out
descriptionToSynth (SynthDescription "identity" _ desc out) =
  IdentitySynth
    . Identity (fromMaybe (identityDesc defaultIdentity) desc)
    $ maybe (identityOutput defaultIdentity) fromText out
descriptionToSynth s =
  error $ "Could not find implementation for synthesiser '" <> show s <> "'"

status :: Result Failed () -> Html
status (Pass _) = H.td ! A.class_ "is-success" $ "Passed"
status (Fail EmptyFail) = H.td ! A.class_ "is-danger" $ "Failed"
status (Fail (EquivFail _)) = H.td ! A.class_ "is-danger" $ "Equivalence failed"
status (Fail (SimFail _)) = H.td ! A.class_ "is-danger" $ "Simulation failed"
status (Fail SynthFail) = H.td ! A.class_ "is-danger" $ "Synthesis failed"
status (Fail EquivError) = H.td ! A.class_ "is-danger" $ "Equivalence error"
status (Fail TimeoutError) = H.td ! A.class_ "is-warning" $ "Time out"

synthStatusHtml :: SynthStatus -> Html
synthStatusHtml (SynthStatus synth res diff) = H.tr $ do
  H.td . H.toHtml $ toText synth
  status res
  H.td . H.toHtml $ showT diff

synthResultHtml :: SynthResult -> Html
synthResultHtml (SynthResult synth1 synth2 res diff) = H.tr $ do
  H.td . H.toHtml $ toText synth1
  H.td . H.toHtml $ toText synth2
  status res
  H.td . H.toHtml $ showT diff

resultHead :: Text -> Html
resultHead name = H.head $ do
  H.title $ "Fuzz Report - " <> H.toHtml name
  H.meta ! A.name "viewport" ! A.content "width=device-width, initial-scale=1"
  H.meta ! A.charset "utf8"
  H.link
    ! A.rel "stylesheet"
    ! A.href
      "https://cdnjs.cloudflare.com/ajax/libs/bulma/0.7.4/css/bulma.min.css"

resultReport :: Text -> FuzzReport -> Html
resultReport name (FuzzReport _ synth _ stat _ _ _ _) = H.docTypeHtml $ do
  resultHead name
  H.body
    . (H.section ! A.class_ "section")
    . (H.div ! A.class_ "container")
    $ do
      H.h1 ! A.class_ "title is-1" $ "Fuzz Report - " <> H.toHtml name
      H.h2 ! A.class_ "title is-2" $ "Synthesis"
      H.table ! A.class_ "table" $ do
        H.thead
          . H.toHtml
          $ ( H.tr
                . H.toHtml
                $ [H.th "Tool", H.th "Status", H.th "Run time"]
            )
        H.tbody . H.toHtml $ fmap synthStatusHtml stat
      H.h2 ! A.class_ "title is-2" $ "Equivalence Check"
      H.table ! A.class_ "table" $ do
        H.thead
          . H.toHtml
          $ ( H.tr
                . H.toHtml
                $ [ H.th "First tool",
                    H.th "Second tool",
                    H.th "Status",
                    H.th "Run time"
                  ]
            )
        H.tbody . H.toHtml $ fmap synthResultHtml synth

resultStatus :: Result a b -> Html
resultStatus (Pass _) = H.td ! A.class_ "is-success" $ "Passed"
resultStatus (Fail _) = H.td ! A.class_ "is-danger" $ "Failed"

meanVariance :: [Double] -> (Double, Double)
meanVariance l = (mean, variance)
  where
    mean = sum l / len
    variance = sum (squ . subtract mean <$> l) / (len - 1.0)
    squ x = x * x
    len = fromIntegral $ length l

fuzzStats ::
  (Real a1, Traversable t) =>
  ((a1 -> Const (Endo [a1]) a1) -> a2 -> Const (Endo [a1]) a2) ->
  t a2 ->
  (Double, Double)
fuzzStats sel fr = meanVariance converted
  where
    converted = fmap realToFrac $ fr ^.. traverse . sel

fuzzStatus :: Text -> FuzzReport -> Html
fuzzStatus name (FuzzReport dir s1 s2 s3 sz t1 t2 t3) = H.tr $ do
  H.td
    . ( H.a
          ! A.href
            ( H.textValue $
                toTextIgnore (dir <.> "html")
            )
      )
    $ H.toHtml name
  resultStatus $
    mconcat (fmap getSynthResult s1)
      <> mconcat (fmap getSimResult s2)
      <> mconcat (fmap getSynthStatus s3)
  H.td . H.string $ show sz
  H.td . H.string $ show t1
  H.td . H.string $ show t2
  H.td . H.string $ show t3

summary :: Text -> [FuzzReport] -> Html
summary name fuzz = H.docTypeHtml $ do
  resultHead name
  H.body
    . (H.section ! A.class_ "section")
    . (H.div ! A.class_ "container")
    $ do
      H.h1 ! A.class_ "title is-1" $ "FuzzReport - " <> H.toHtml name
      H.table ! A.class_ "table" $ do
        H.thead . H.tr $
          H.toHtml
            [ H.th "Name",
              H.th "Status",
              H.th "Size (loc)",
              H.th "Synthesis time",
              H.th "Equivalence check time",
              H.th "Reduction time"
            ]
        H.tbody
          . H.toHtml
          . fmap
            ( \(i, r) ->
                fuzzStatus ("Fuzz " <> showT (i :: Int)) r
            )
          $ zip [1 ..] fuzz
        H.tfoot . H.toHtml $ do
          H.tr $
            H.toHtml
              [ H.td $ H.strong "Total",
                H.td mempty,
                H.td
                  . H.string
                  . show
                  . sum
                  $ fuzz
                    ^.. traverse
                    . fileLines,
                sumUp synthTime,
                sumUp equivTime,
                sumUp reducTime
              ]
          H.tr $
            H.toHtml
              [ H.td $ H.strong "Mean",
                H.td mempty,
                fst $ bimap d2I d2I $ fuzzStats fileLines fuzz,
                fst $ meanVar synthTime,
                fst $ meanVar equivTime,
                fst $ meanVar reducTime
              ]
          H.tr $
            H.toHtml
              [ H.td $ H.strong "Variance",
                H.td mempty,
                snd $ bimap d2I d2I $ fuzzStats fileLines fuzz,
                snd $ meanVar synthTime,
                snd $ meanVar equivTime,
                snd $ meanVar reducTime
              ]
  where
    sumUp s = showHtml . sum $ fuzz ^.. traverse . s
    meanVar s = bimap d2T d2T $ fuzzStats s fuzz
    showHtml = H.td . H.string . show
    d2T = showHtml . (realToFrac :: Double -> NominalDiffTime)
    d2I = H.td . H.string . show

printResultReport :: Text -> FuzzReport -> Text
printResultReport t f = toStrict . renderHtml $ resultReport t f

printSummary :: Text -> [FuzzReport] -> Text
printSummary t f = toStrict . renderHtml $ summary t f