aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorYann Herklotz <git@yannherklotz.com>2021-05-21 18:30:14 +0100
committerYann Herklotz <git@yannherklotz.com>2021-05-21 18:30:14 +0100
commit6547ca0b1d6244fcced31ce119ff5841cb60b086 (patch)
treea0c11d626cc6641436961fb76093c8919f3acfeb /src
parentc098e8c2e2ed1f5defc5811a76109eeed34c4d74 (diff)
downloadverismith-6547ca0b1d6244fcced31ce119ff5841cb60b086.tar.gz
verismith-6547ca0b1d6244fcced31ce119ff5841cb60b086.zip
Add functions and fix EMI
Diffstat (limited to 'src')
-rw-r--r--src/Verismith/EMI.hs27
-rw-r--r--src/Verismith/Fuzz.hs40
2 files changed, 51 insertions, 16 deletions
diff --git a/src/Verismith/EMI.hs b/src/Verismith/EMI.hs
index aca7e48..cd216a6 100644
--- a/src/Verismith/EMI.hs
+++ b/src/Verismith/EMI.hs
@@ -41,7 +41,7 @@ import qualified Data.Text.IO as T
data EMIInputs a = EMIInputs [Identifier]
| EMIOrig a
- deriving (Eq)
+ deriving (Eq, Ord)
instance Show a => Show (EMIInputs a) where
show (EMIInputs i) = "EMI: " <> intercalate ", " (T.unpack . getIdentifier <$> i)
@@ -78,9 +78,15 @@ moditemEMI m = return m
moddeclEMI :: ModDecl a -> StateGen a (ModDecl (EMIInputs a))
moddeclEMI m = do
emiContext._Just.emiNewInputs .= []
+ blocking .= []
+ nonblocking .= []
+ wires .= []
m' <- traverseOf (modItems.traverse) moditemEMI m
c <- use (emiContext._Just.emiNewInputs)
- let m'' = m' & modInPorts %~ (c ++ ) & (initNewRegs c)
+ b <- use blocking
+ nb <- use nonblocking
+ w <- use wires
+ let m'' = m' & modInPorts %~ (c ++ ) & initNewRegs c & initNewInnerRegs (b <> nb <> w)
return (ModDeclAnn (EMIInputs (c^..traverse.portName)) (fmap (\x -> EMIOrig x) m''))
sourceEMI :: (SourceInfo a) -> StateGen a (SourceInfo (EMIInputs a))
@@ -90,6 +96,9 @@ sourceEMI s =
initNewRegs :: [Port] -> ModDecl a -> ModDecl a
initNewRegs ps m = m & modItems %~ (++ (Decl (Just PortIn) <$> ps <*> pure Nothing))
+initNewInnerRegs :: [Port] -> ModDecl a -> ModDecl a
+initNewInnerRegs ps m = m & modItems %~ (++ (Decl Nothing <$> ps <*> pure Nothing))
+
-- | Procedural generation method for random Verilog. Uses internal 'Reader' and
-- 'State' to keep track of the current Verilog code structure.
proceduralEMI :: SourceInfo a -> Config -> Gen (SourceInfo (EMIInputs a))
@@ -102,7 +111,7 @@ proceduralEMI src config = do
return mainMod
where
context =
- Context [] [] [] [] [] [] 0 (confProp propStmntDepth) (confProp propModDepth) True
+ Context [] [] [] [] [] [] 100000 (confProp propStmntDepth) (confProp propModDepth) True
(Just (EMIContext []))
num = fromIntegral $ confProp propSize
confProp i = config ^. configProperty . i
@@ -166,6 +175,12 @@ initModEMI (m, i) = m & modItems %~ ((out ++ inp ++ other) ++)
inp = Decl (Just PortIn) <$> (m^.modInPorts) <*> pure Nothing
other = Decl Nothing <$> map (\i' -> Port Reg False (Range 0 0) i') i <*> pure Nothing
+getTopEMIIdent :: SourceInfo (EMIInputs a) -> [Identifier]
+getTopEMIIdent s = concatMap (\x -> case x of
+ EMIInputs x -> x
+ _ -> []
+ ) (collectAnn (s^.mainModule))
+
-- Test code
m :: SourceInfo ()
@@ -193,8 +208,12 @@ endmodule
p :: Show a => ModDecl a -> IO ()
p = T.putStrLn . genSource
+p2 :: Show a => SourceInfo a -> IO ()
+p2 = T.putStrLn . genSource
+
customConfig = defaultConfig &
(configEMI . confEMIGenerateProb .~ 1)
. (configEMI . confEMINoGenerateProb .~ 0)
-top = ((initModEMI . makeTopAssertEMI False . (\s -> s^.mainModule)) <$> proceduralEMIIO m customConfig) >>= p
+top = ((initModEMI . makeTopAssertEMI True . (\s -> s^.mainModule)) <$> proceduralEMIIO m customConfig) >>= p
+top2 = proceduralEMIIO m customConfig >>= p2
diff --git a/src/Verismith/Fuzz.hs b/src/Verismith/Fuzz.hs
index c2c30a9..89a1e39 100644
--- a/src/Verismith/Fuzz.hs
+++ b/src/Verismith/Fuzz.hs
@@ -18,6 +18,7 @@ module Verismith.Fuzz
fuzz,
fuzzInDir,
fuzzMultiple,
+ fuzzMultipleEMI,
runFuzz,
sampleSeed,
@@ -62,6 +63,7 @@ import Verismith.Tool.Yosys
import Verismith.Utils (generateByteString)
import Verismith.Verilog.AST
import Verismith.Verilog.CodeGen
+import Verismith.EMI
import Prelude hiding (FilePath)
data FuzzOpts
@@ -361,12 +363,12 @@ simulation src = do
where
dir = fromText $ "countereg_sim_" <> toText a
-simulationEMI :: (MonadIO m, MonadSh m, Show ann) => (SourceInfo ann) -> Fuzz m ()
+simulationEMI :: (MonadIO m, MonadSh m, Show ann) => (SourceInfo (EMIInputs ann)) -> Fuzz m ()
simulationEMI src = do
datadir <- fmap _fuzzDataDir askOpts
synth <- passedSynthesis
counterEgs <- failEquivWithIdentityCE
- vals <- liftIO $ generateByteString Nothing 32 20
+ vals <- liftIO $ generateByteString Nothing 32 100
ident <- liftSh $ sim datadir vals Nothing defaultIdentitySynth
resTimes <- liftSh $ mapM (sim datadir vals (justPass $ snd ident)) synth
fuzzSimResults .= toSimResult defaultIcarusSim vals synth resTimes
@@ -382,9 +384,9 @@ simulationEMI src = do
cp (fromText ".." </> fromText (toText a) </> synthOutput a) $
synthOutput a
writefile "rtl.v" $ genSource src
- runSimIc datadir defaultIcarus a src b i
+ runSimIcEMI (getTopEMIIdent src) datadir defaultIcarus a (clearAnn src) b i
where
- dir = fromText $ "countereg_sim_" <> toText a
+ dir = fromText $ "emi_sim_" <> toText a
failEquivWithIdentity :: (MonadSh m) => Fuzz m [SynthResult]
failEquivWithIdentity = filter withIdentity . _fuzzSynthResults <$> get
@@ -550,12 +552,14 @@ fuzz gen = do
(getTime redResult)
return report
-fuzzInDir :: (MonadFuzz m, Ord ann, Show ann) => Gen (SourceInfo ann) -> Fuzz m FuzzReport
-fuzzInDir src = do
+fuzzInDirG :: (MonadFuzz m, Ord ann, Show ann) =>
+ (Gen (SourceInfo ann) -> Fuzz m FuzzReport) ->
+ Gen (SourceInfo ann) -> Fuzz m FuzzReport
+fuzzInDirG f src = do
fuzzOpts <- askOpts
let fp = fromMaybe "fuzz" $ _fuzzOptsOutput fuzzOpts
make fp
- res <- pop fp $ fuzz src
+ res <- pop fp $ f src
liftSh $ do
writefile (fp <.> "html") $ printResultReport (bname fp) res
when (passedFuzz res && not (_fuzzOptsKeepAll fuzzOpts)) $ rm_rf fp
@@ -563,11 +567,12 @@ fuzzInDir src = do
where
bname = T.pack . takeBaseName . T.unpack . toTextIgnore
-fuzzMultiple ::
+fuzzMultipleG ::
(MonadFuzz m, Ord ann, Show ann) =>
+ (Gen (SourceInfo ann) -> Fuzz m FuzzReport) ->
Gen (SourceInfo ann) ->
Fuzz m [FuzzReport]
-fuzzMultiple src = do
+fuzzMultipleG f src = do
fuzzOpts <- askOpts
let seed = (_fuzzOptsConfig fuzzOpts) ^. configProperty . propSeed
x <- case _fuzzOptsOutput fuzzOpts of
@@ -591,13 +596,12 @@ fuzzMultiple src = do
results
return results
where
- fuzzDir' :: (Show a, MonadFuzz m) => a -> Fuzz m FuzzReport
fuzzDir' n' =
local
( fuzzEnvOpts . fuzzOptsOutput
.~ (Just . fromText $ "fuzz_" <> showT n')
)
- $ fuzzInDir src
+ $ fuzzInDirG f src
sampleSeed :: MonadSh m => Maybe Seed -> Gen a -> m (Seed, a)
sampleSeed s gen =
@@ -616,7 +620,7 @@ sampleSeed s gen =
pure (seed, Hog.treeValue x)
in loop (100 :: Int)
-fuzzEMI :: (MonadFuzz m, Ord ann, Show ann) => Gen (SourceInfo ann) -> Fuzz m FuzzReport
+fuzzEMI :: (MonadFuzz m, Ord ann, Show ann) => Gen (SourceInfo (EMIInputs ann)) -> Fuzz m FuzzReport
fuzzEMI gen = do
conf <- askConfig
opts <- askOpts
@@ -652,3 +656,15 @@ fuzzEMI gen = do
0
0
return report
+
+fuzzInDir :: (MonadFuzz m, Ord ann, Show ann) => Gen (SourceInfo ann) -> Fuzz m FuzzReport
+fuzzInDir = fuzzInDirG fuzz
+
+fuzzInDirEMI :: (MonadFuzz m, Ord ann, Show ann) => Gen (SourceInfo (EMIInputs ann)) -> Fuzz m FuzzReport
+fuzzInDirEMI = fuzzInDirG fuzzEMI
+
+fuzzMultiple :: (MonadFuzz m, Ord ann, Show ann) => Gen (SourceInfo ann) -> Fuzz m [FuzzReport]
+fuzzMultiple = fuzzMultipleG fuzz
+
+fuzzMultipleEMI :: (MonadFuzz m, Ord ann, Show ann) => Gen (SourceInfo (EMIInputs ann)) -> Fuzz m [FuzzReport]
+fuzzMultipleEMI = fuzzMultipleG fuzzEMI