aboutsummaryrefslogtreecommitdiffstats
path: root/src/Verismith/EMI.hs
blob: 555e3717f7a1bf4edf5b2419a0778e1299110f6b (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
{-# LANGUAGE QuasiQuotes #-}

-- |
-- Module      : Verismith.EMI
-- Description : Definition of the circuit graph.
-- Copyright   : (c) 2021, Yann Herklotz
-- License     : GPL-3
-- Maintainer  : yann [at] yannherklotz [dot] com
-- Stability   : experimental
-- Portability : POSIX
--
-- Equivalence modulo inputs (EMI) testing.  This file should get an existing design, and spit out a
-- modified design that is equivalent under some specific values of the extra inputs.
module Verismith.EMI
  ( genEMI,
  )
where

import Control.Lens hiding (Context)
import Control.Monad (replicateM)
import Control.Monad.Reader
import Control.Monad.State.Strict
import Data.Text (Text)
import qualified Data.Text as T
import Hedgehog (Gen, GenT, MonadGen)
import qualified Hedgehog as Hog
import qualified Hedgehog.Gen as Hog
import qualified Hedgehog.Range as HogR
import Data.Maybe (fromMaybe)
import Verismith.Config
import Verismith.Internal
import Verismith.Verilog.AST
import Verismith.Verilog.BitVec
import Verismith.Verilog.Eval
import Verismith.Verilog.Internal
import Verismith.Verilog.Mutate
import Verismith.Generate

import Verismith.Verilog.CodeGen
import Verismith.Verilog.Quote
import qualified Data.Text.IO as T

newPort' :: Identifier -> StateGen a Port
newPort' ident = do
  hex <- Identifier . T.toLower . T.pack <$> Hog.list (HogR.constant 10 10) Hog.hexit
  let p = Port Wire False (Range 0 0) (ident <> hex)
  emiContext . _Just . emiNewInputs %= (p :)
  return p

nstatementEMI :: StateGen a (Maybe (Statement a))
nstatementEMI = do
  config <- ask
  Hog.frequency
    [ (config ^. configEMI . confEMIGenerateProb, do
          s' <- statement
          n <- newPort' "emi_"
          return (Just (CondStmnt (Id (n^.portName)) (Just s') Nothing))),
      (config ^. configEMI . confEMINoGenerateProb, return Nothing)
    ]

statementEMI :: Statement a -> StateGen a (Statement a)
statementEMI (SeqBlock s) = do
  s'' <- nstatementEMI
  return $ SeqBlock ((s'' ^.. _Just) ++ s)
statementEMI s = return s

moditemEMI :: ModItem a -> StateGen a (ModItem a)
moditemEMI (Always s) = Always <$> transformM statementEMI s
moditemEMI m = return m

genEMI :: (ModDecl a) -> StateGen a (ModDecl a)
genEMI (ModDecl mid outp inp itms params) = do
  itms' <- traverse moditemEMI itms
  return (ModDecl mid outp inp itms' params)

initNewRegs :: [Port] -> ModDecl a -> ModDecl a
initNewRegs ps m = m & modItems %~ (++ (Decl (Just PortIn) <$> ps <*> pure Nothing))

-- | Procedural generation method for random Verilog. Uses internal 'Reader' and
-- 'State' to keep track of the current Verilog code structure.
proceduralEMI :: ModDecl a -> Config -> Gen (ModDecl a)
proceduralEMI moddecl config = do
  (mainMod, st) <-
    Hog.resize num $
      runStateT
        (Hog.distributeT (runReaderT (genEMI moddecl) config))
        context
  let addMod = modInPorts %~ ((st ^. emiContext . _Just . emiNewInputs) ++ )
  let initMod = initNewRegs (st ^. emiContext . _Just . emiNewInputs)
  return (initMod $ addMod mainMod)
  where
    context =
      Context [] [] [] [] [] [] 0 (confProp propStmntDepth) (confProp propModDepth) True
        (Just (EMIContext []))
    num = fromIntegral $ confProp propSize
    confProp i = config ^. configProperty . i

proceduralEMIIO :: ModDecl () -> Config -> IO (ModDecl ())
proceduralEMIIO t = Hog.sample . proceduralEMI t

-- m = (head . head $ [verilog|
-- module m;
--   always @(posedge clk) begin
--     if (z == 2) begin
--       ry = 2;
--     end
--     x <= y;
--     y <= z;
--   end
-- endmodule
-- |] ^.. _Wrapped )
-- p :: Show a => ModDecl a -> IO ()
-- p = T.putStrLn . genSource
--
-- customConfig = defaultConfig &
--     (configEMI . confEMIGenerateProb .~ 1)
--   . (configEMI . confEMINoGenerateProb .~ 0)