aboutsummaryrefslogtreecommitdiffstats
path: root/src/Verismith/EMI.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Verismith/EMI.hs')
-rw-r--r--src/Verismith/EMI.hs33
1 files changed, 23 insertions, 10 deletions
diff --git a/src/Verismith/EMI.hs b/src/Verismith/EMI.hs
index a96496e..6891eda 100644
--- a/src/Verismith/EMI.hs
+++ b/src/Verismith/EMI.hs
@@ -25,7 +25,7 @@ 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 Hog
+import qualified Hedgehog.Range as HogR
import Data.Maybe (fromMaybe)
import Verismith.Config
import Verismith.Internal
@@ -42,21 +42,30 @@ import qualified Data.Text.IO as T
newPort' :: Identifier -> StateGen a Port
newPort' ident = do
- let p = Port Wire False (Range 1 1) ident
+ 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' <- statement
- n <- newPort' "x"
- let s'' = CondStmnt (Id "x") (Just s') Nothing
- return $ SeqBlock (s'' : s)
-statementEMI (EventCtrl e (Just s)) = EventCtrl e . Just <$> (statementEMI s)
+ s'' <- nstatementEMI
+ return $ SeqBlock ((s'' ^.. _Just) ++ s)
statementEMI s = return s
moditemEMI :: ModItem a -> StateGen a (ModItem a)
-moditemEMI (Always s) = Always <$> statementEMI s
+moditemEMI (Always s) = Always <$> transformM statementEMI s
moditemEMI m = return m
genEMI :: (ModDecl a) -> StateGen a (ModDecl a)
@@ -64,6 +73,9 @@ 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)
@@ -73,8 +85,9 @@ proceduralEMI moddecl config = do
runStateT
(Hog.distributeT (runReaderT (genEMI moddecl) config))
context
- let mainMod' = mainMod & modInPorts %~ (++ (st ^. emiContext . _Just . emiNewInputs))
- return mainMod'
+ 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