aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--src/VeriFuzz/Config.hs99
-rw-r--r--src/VeriFuzz/Reduce.hs18
-rw-r--r--src/VeriFuzz/Verilog/Gen.hs35
3 files changed, 55 insertions, 97 deletions
diff --git a/src/VeriFuzz/Config.hs b/src/VeriFuzz/Config.hs
index 8f1c869..f4656ec 100644
--- a/src/VeriFuzz/Config.hs
+++ b/src/VeriFuzz/Config.hs
@@ -21,8 +21,6 @@ module VeriFuzz.Config
, Probability(..)
-- *** Expression
, ProbExpr(..)
- -- *** Event List
- , ProbEventList(..)
-- *** Module Item
, ProbModItem(..)
-- *** Statement
@@ -45,7 +43,6 @@ module VeriFuzz.Config
, probModItem
, probStmnt
, probExpr
- , probEventList
, probExprNum
, probExprId
, probExprRangeSelect
@@ -56,11 +53,9 @@ module VeriFuzz.Config
, probExprStr
, probExprSigned
, probExprUnsigned
- , probEventListAll
- , probEventListVar
- , probEventListClk
, probModItemAssign
- , probModItemAlways
+ , probModItemSeqAlways
+ , probModItemCombAlways
, probModItemInst
, probStmntBlock
, probStmntNonBlock
@@ -137,9 +132,6 @@ import VeriFuzz.Sim.Yosys
-- >>> T.putStrLn $ encodeConfig defaultConfig
-- <BLANKLINE>
-- [probability]
--- eventlist.all = 0
--- eventlist.clk = 1
--- eventlist.var = 0
-- expr.binary = 5
-- expr.concatenation = 3
-- expr.number = 1
@@ -150,9 +142,10 @@ import VeriFuzz.Sim.Yosys
-- expr.unary = 5
-- expr.unsigned = 5
-- expr.variable = 5
--- moditem.always = 1
-- moditem.assign = 5
+-- moditem.combinational = 1
-- moditem.instantiation = 1
+-- moditem.sequential = 1
-- statement.blocking = 0
-- statement.conditional = 1
-- statement.forloop = 0
@@ -208,11 +201,13 @@ data ProbExpr = ProbExpr { _probExprNum :: {-# UNPACK #-} !Int
deriving (Eq, Show)
-- | Probability of generating different nodes inside a module declaration.
-data ProbModItem = ProbModItem { _probModItemAssign :: {-# UNPACK #-} !Int
+data ProbModItem = ProbModItem { _probModItemAssign :: {-# UNPACK #-} !Int
-- ^ Probability of generating an @assign@.
- , _probModItemAlways :: {-# UNPACK #-} !Int
- -- ^ Probability of generating an @always@ block.
- , _probModItemInst :: {-# UNPACK #-} !Int
+ , _probModItemSeqAlways :: {-# UNPACK #-} !Int
+ -- ^ Probability of generating a sequential @always@ block.
+ , _probModItemCombAlways :: {-# UNPACK #-} !Int
+ -- ^ Probability of generating an combinational @always@ block.
+ , _probModItemInst :: {-# UNPACK #-} !Int
-- ^ Probability of generating a module
-- instantiation.
}
@@ -225,16 +220,9 @@ data ProbStatement = ProbStatement { _probStmntBlock :: {-# UNPACK #-} !Int
}
deriving (Eq, Show)
-data ProbEventList = ProbEventList { _probEventListAll :: {-# UNPACK #-} !Int
- , _probEventListClk :: {-# UNPACK #-} !Int
- , _probEventListVar :: {-# UNPACK #-} !Int
- }
- deriving (Eq, Show)
-
-data Probability = Probability { _probModItem :: {-# UNPACK #-} !ProbModItem
- , _probStmnt :: {-# UNPACK #-} !ProbStatement
- , _probExpr :: {-# UNPACK #-} !ProbExpr
- , _probEventList :: {-# UNPACK #-} !ProbEventList
+data Probability = Probability { _probModItem :: {-# UNPACK #-} !ProbModItem
+ , _probStmnt :: {-# UNPACK #-} !ProbStatement
+ , _probExpr :: {-# UNPACK #-} !ProbExpr
}
deriving (Eq, Show)
@@ -250,32 +238,31 @@ data SimDescription = SimDescription { simName :: {-# UNPACK #-} !Text }
deriving (Eq, Show)
data SynthDescription = SynthDescription { synthName :: {-# UNPACK #-} !Text
- , synthYosysBin :: !(Maybe Text)
- , synthYosysDesc :: !(Maybe Text)
- , synthYosysOutput :: !(Maybe Text)
- , synthXstBin :: !(Maybe Text)
- , synthXstDesc :: !(Maybe Text)
- , synthXstOutput :: !(Maybe Text)
- , synthVivadoBin :: !(Maybe Text)
- , synthVivadoDesc :: !(Maybe Text)
- , synthVivadoOutput :: !(Maybe Text)
- , synthQuartusBin :: !(Maybe Text)
- , synthQuartusDesc :: !(Maybe Text)
- , synthQuartusOutput :: !(Maybe Text)
+ , synthYosysBin :: Maybe Text
+ , synthYosysDesc :: Maybe Text
+ , synthYosysOutput :: Maybe Text
+ , synthXstBin :: Maybe Text
+ , synthXstDesc :: Maybe Text
+ , synthXstOutput :: Maybe Text
+ , synthVivadoBin :: Maybe Text
+ , synthVivadoDesc :: Maybe Text
+ , synthVivadoOutput :: Maybe Text
+ , synthQuartusBin :: Maybe Text
+ , synthQuartusDesc :: Maybe Text
+ , synthQuartusOutput :: Maybe Text
}
deriving (Eq, Show)
data Config = Config { _configProbability :: {-# UNPACK #-} !Probability
, _configProperty :: {-# UNPACK #-} !Property
- , _configSimulators :: ![SimDescription]
- , _configSynthesisers :: ![SynthDescription]
+ , _configSimulators :: [SimDescription]
+ , _configSynthesisers :: [SynthDescription]
}
deriving (Eq, Show)
makeLenses ''ProbExpr
makeLenses ''ProbModItem
makeLenses ''ProbStatement
-makeLenses ''ProbEventList
makeLenses ''Probability
makeLenses ''Property
makeLenses ''Config
@@ -356,15 +343,16 @@ fromQuartus (Quartus a b c) =
(Just $ toTextIgnore c)
defaultConfig :: Config
-defaultConfig = Config (Probability defModItem defStmnt defExpr defEvent)
+defaultConfig = Config (Probability defModItem defStmnt defExpr)
(Property 20 Nothing 3 2 5)
[]
[fromYosys defaultYosys, fromVivado defaultVivado]
where
defModItem =
ProbModItem 5 -- Assign
- 1 -- Always
- 1 -- Instantiation
+ 1 -- Sequential Always
+ 1 -- Combinational Always
+ 1 -- Instantiation
defStmnt =
ProbStatement 0 -- Blocking assignment
3 -- Non-blocking assignment
@@ -381,10 +369,6 @@ defaultConfig = Config (Probability defModItem defStmnt defExpr defEvent)
0 -- String
5 -- Signed function
5 -- Unsigned funtion
- defEvent =
- ProbEventList 0 -- All
- 1 -- Clk
- 0 -- Var
twoKey :: Toml.Piece -> Toml.Piece -> Toml.Key
twoKey a b = Toml.Key (a :| [b])
@@ -439,27 +423,16 @@ modItemCodec =
ProbModItem
<$> defaultValue (defProb probModItemAssign) (intM "assign")
.= _probModItemAssign
- <*> defaultValue (defProb probModItemAlways) (intM "always")
- .= _probModItemAlways
+ <*> defaultValue (defProb probModItemSeqAlways) (intM "sequential")
+ .= _probModItemSeqAlways
+ <*> defaultValue (defProb probModItemCombAlways) (intM "combinational")
+ .= _probModItemCombAlways
<*> defaultValue (defProb probModItemInst) (intM "instantiation")
.= _probModItemInst
where
defProb i = defaultConfig ^. configProbability . probModItem . i
intM = int "moditem"
-eventListCodec :: TomlCodec ProbEventList
-eventListCodec =
- ProbEventList
- <$> defaultValue (defProb probEventListClk) (intE "clk")
- .= _probEventListClk
- <*> defaultValue (defProb probEventListAll) (intE "all")
- .= _probEventListAll
- <*> defaultValue (defProb probEventListVar) (intE "var")
- .= _probEventListVar
- where
- defProb i = defaultConfig ^. configProbability . probEventList . i
- intE = int "eventlist"
-
probCodec :: TomlCodec Probability
probCodec =
Probability
@@ -469,8 +442,6 @@ probCodec =
.= _probStmnt
<*> defaultValue (defProb probExpr) exprCodec
.= _probExpr
- <*> defaultValue (defProb probEventList) eventListCodec
- .= _probEventList
where defProb i = defaultConfig ^. configProbability . i
propCodec :: TomlCodec Property
diff --git a/src/VeriFuzz/Reduce.hs b/src/VeriFuzz/Reduce.hs
index 49d4dc9..8b3c9c5 100644
--- a/src/VeriFuzz/Reduce.hs
+++ b/src/VeriFuzz/Reduce.hs
@@ -23,6 +23,8 @@ import VeriFuzz.Verilog.AST
import VeriFuzz.Verilog.CodeGen
import VeriFuzz.Verilog.Mutate
+-- | Replacement type that supports returning different kinds of reduced
+-- replacements that could be tried.
data Replacement a = Dual a a
| Single a
| None
@@ -58,21 +60,30 @@ halve [] = None
halve [a] = Single [a]
halve l = Dual a b where (a, b) = splitAt (length l `div` 2) l
+-- | When given a Lens and a function that works on a lower replacement, it will
+-- go down, apply the replacement, and return a replacement of the original
+-- module.
combine :: Lens' a b -> (b -> Replacement b) -> a -> Replacement a
combine l f i = modify <$> f (i ^. l) where modify res = i & l .~ res
+-- | Deletes Id 'Expr' if they are not part of the current scope, and replaces
+-- these by 0.
filterExpr :: [Identifier] -> Expr -> Expr
filterExpr ids (Id i) = if i `notElem` ids then Number 0 else Id i
filterExpr _ e = e
+-- | Checks if a declaration is part of the current scope. If not, it returns
+-- 'False', otherwise 'True', as it should be kept.
filterDecl :: [Identifier] -> ModItem -> Bool
filterDecl ids (Decl Nothing (Port _ _ _ i) _) = i `elem` ids
filterDecl _ _ = True
+-- | Checks if a continuous assignment is in the current scope, if not, it
+-- returns 'False'.
filterAssigns :: [Port] -> ModItem -> Bool
filterAssigns out (ModCA (ContAssign i _)) =
- notElem i $ out ^.. traverse . portName
-filterAssigns _ _ = False
+ elem i $ out ^.. traverse . portName
+filterAssigns _ _ = True
cleanUndefined :: [Identifier] -> [ModItem] -> [ModItem]
cleanUndefined ids mis =
@@ -163,7 +174,8 @@ reduce_ repl eval src = do
. modContAssign
eval m
--- | Reduce an input to a minimal representation.
+-- | Reduce an input to a minimal representation. It first reduces the always
+-- blocks, then reduces
reduce
:: (SourceInfo -> IO Bool) -- ^ Failed or not.
-> SourceInfo -- ^ Input verilog source to be reduced.
diff --git a/src/VeriFuzz/Verilog/Gen.hs b/src/VeriFuzz/Verilog/Gen.hs
index 7b9c31b..feb2be5 100644
--- a/src/VeriFuzz/Verilog/Gen.hs
+++ b/src/VeriFuzz/Verilog/Gen.hs
@@ -29,7 +29,6 @@ import Control.Monad.Trans.Reader hiding (local)
import Control.Monad.Trans.State.Strict
import Data.Foldable (fold)
import Data.Functor.Foldable (cata)
-import Data.List.NonEmpty (NonEmpty (..), toList)
import qualified Data.Text as T
import Hedgehog (Gen)
import qualified Hedgehog.Gen as Hog
@@ -100,7 +99,7 @@ gen :: Gen a -> StateGen a
gen = lift . lift
listOf1 :: Gen a -> Gen [a]
-listOf1 a = toList <$> Hog.nonEmpty (Hog.linear 0 100) a
+listOf1 a = Hog.list (Hog.linear 1 100) a
--listOf :: Gen a -> Gen [a]
--listOf = Hog.list (Hog.linear 0 100)
@@ -349,34 +348,10 @@ statement = do
]
where onDepth c n = if c ^. stmntDepth > 0 then n else 0
-recEventList :: NonEmpty Identifier -> Hog.Size -> Gen Event
-recEventList ids size
- | size <= 0 = idgen
- | otherwise = Hog.choice [idgen, EOr <$> recCall <*> recCall]
- where
- idgen = fmap EId . Hog.element $ toList ids
- recCall = recEventList ids (size `div` 2)
-
-eventList :: StateGen Event
-eventList = do
- prob <- askProbability
- context <- get
- let defProb i = prob ^. probEventList . i
- gen $ Hog.frequency
- [ (defProb probEventListAll, return EAll)
- , ( defProb probEventListVar
- , case context ^. variables of
- [] -> return EAll
- x : xs -> Hog.sized . recEventList $ fromPort <$> (x :| xs)
- )
- , (defProb probEventListClk, return $ EPosEdge "clk")
- ]
-
-always :: StateGen ModItem
-always = do
- events <- eventList
+alwaysSeq :: StateGen ModItem
+alwaysSeq = do
stat <- seqBlock
- return $ Always (EventCtrl events (Just stat))
+ return $ Always (EventCtrl (EPosEdge "clk") (Just stat))
instantiate :: ModDecl -> StateGen ModItem
instantiate (ModDecl i outP inP _ _) = do
@@ -446,7 +421,7 @@ modItem = do
let defProb i = prob ^. probModItem . i
Hog.frequency
[ (defProb probModItemAssign, ModCA <$> contAssign)
- , (defProb probModItemAlways, always)
+ , (defProb probModItemSeqAlways, alwaysSeq)
, ( if context ^. modDepth > 0 then defProb probModItemInst else 0
, modInst
)