aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorYann Herklotz <git@yannherklotz.com>2019-07-27 00:57:44 +0200
committerYann Herklotz <git@yannherklotz.com>2019-07-27 00:57:44 +0200
commit7e5621f79dfbeb2e5112bef931c4cfc858a2f19e (patch)
tree03677dc06c19f6c188446661a51c158adafc83a8
parent7777952f38b24f26f29c2327296494f32d5f49a9 (diff)
downloadverismith-7e5621f79dfbeb2e5112bef931c4cfc858a2f19e.tar.gz
verismith-7e5621f79dfbeb2e5112bef931c4cfc858a2f19e.zip
Add a benchmark
-rw-r--r--default.nix18
-rw-r--r--src/VeriFuzz/Generate.hs112
-rw-r--r--src/VeriFuzz/Verilog/AST.hs95
-rw-r--r--src/VeriFuzz/Verilog/BitVec.hs6
-rw-r--r--test/Benchmark.hs14
-rw-r--r--verifuzz.cabal12
6 files changed, 196 insertions, 61 deletions
diff --git a/default.nix b/default.nix
index db81294..027ff1b 100644
--- a/default.nix
+++ b/default.nix
@@ -1,11 +1,12 @@
{ mkDerivation, alex, array, base, binary, blaze-html, bytestring
-, Cabal, cabal-doctest, cryptonite, deepseq, DRBG, exceptions, fgl
-, fgl-visualize, filepath, gitrev, hedgehog, hedgehog-fn, lens
-, lifted-base, memory, monad-control, optparse-applicative, parsec
-, prettyprinter, random, recursion-schemes, shakespeare, shelly
-, statistics, stdenv, tasty, tasty-hedgehog, tasty-hunit
-, template-haskell, text, time, tomland, transformers
-, transformers-base, vector
+, Cabal, cabal-doctest, criterion, cryptonite, deepseq, DRBG
+, exceptions, fgl, fgl-visualize, filepath, gitrev, hedgehog
+, hedgehog-fn, lens, lifted-base, memory, monad-control
+, optparse-applicative, parsec, prettyprinter, random
+, recursion-schemes, shakespeare, shelly, statistics, stdenv, tasty
+, tasty-hedgehog, tasty-hunit, template-haskell, text, time
+, tomland, transformers, transformers-base, unordered-containers
+, vector
}:
mkDerivation {
pname = "verifuzz";
@@ -20,7 +21,7 @@ mkDerivation {
lifted-base memory monad-control optparse-applicative parsec
prettyprinter random recursion-schemes shakespeare shelly
statistics template-haskell text time tomland transformers
- transformers-base vector
+ transformers-base unordered-containers vector
];
libraryToolDepends = [ alex ];
executableHaskellDepends = [ base ];
@@ -28,6 +29,7 @@ mkDerivation {
base fgl hedgehog hedgehog-fn lens parsec shakespeare tasty
tasty-hedgehog tasty-hunit text
];
+ benchmarkHaskellDepends = [ base criterion lens ];
homepage = "https://github.com/ymherklotz/VeriFuzz#readme";
description = "Random verilog generation and simulator testing";
license = stdenv.lib.licenses.bsd3;
diff --git a/src/VeriFuzz/Generate.hs b/src/VeriFuzz/Generate.hs
index e2b986b..a82f56b 100644
--- a/src/VeriFuzz/Generate.hs
+++ b/src/VeriFuzz/Generate.hs
@@ -20,6 +20,44 @@ module VeriFuzz.Generate
, proceduralSrc
, proceduralSrcIO
, randomMod
+ -- ** Generate Functions
+ , gen
+ , largeNum
+ , wireSize
+ , range
+ , genBitVec
+ , binOp
+ , unOp
+ , constExprWithContext
+ , exprSafeList
+ , exprRecList
+ , exprWithContext
+ , makeIdentifier
+ , nextPort
+ , newPort
+ , scopedExpr
+ , contAssign
+ , lvalFromPort
+ , assignment
+ , seqBlock
+ , conditional
+ , forLoop
+ , statement
+ , alwaysSeq
+ , instantiate
+ , modInst
+ , modItem
+ , constExpr
+ , parameter
+ , moduleDef
+ -- ** Helpers
+ , someI
+ , probability
+ , askProbability
+ , resizePort
+ , moduleName
+ , evalRange
+ , calcRange
)
where
@@ -43,11 +81,6 @@ import VeriFuzz.Verilog.Eval
import VeriFuzz.Verilog.Internal
import VeriFuzz.Verilog.Mutate
--- Temporary imports
-import Data.Char (toLower)
-import Debug.Trace
-import VeriFuzz.Verilog.CodeGen
-
data Context = Context { _variables :: [Port]
, _parameters :: [Parameter]
, _modules :: [ModDecl]
@@ -103,21 +136,45 @@ randomMod inps total = do
end = drop inps
start = take inps
+-- | Converts a 'Port' to an 'LVal' by only keeping the 'Identifier' of the
+-- 'Port'.
+lvalFromPort :: Port -> LVal
+lvalFromPort (Port _ _ _ i) = RegId i
+
+-- | Returns the probability from the configuration.
+probability :: Config -> Probability
+probability c = c ^. configProbability
+
+-- | Gets the current probabilities from the 'State'.
+askProbability :: StateGen Probability
+askProbability = lift $ asks probability
+
+-- | Lifts a 'Gen' into the 'StateGen' monad.
gen :: Gen a -> StateGen a
gen = lift . lift
+-- | Generates a random large number, which can also be negative.
largeNum :: Gen Int
largeNum = Hog.int $ Hog.linear (-100) 100
+-- | Generates a random size for a wire so that it is not too small and not too
+-- large.
wireSize :: Gen Int
wireSize = Hog.int $ Hog.linear 2 100
+-- | Generates a random range by using the 'wireSize' and 0 as the lower bound.
range :: Gen Range
range = Range <$> fmap fromIntegral wireSize <*> pure 0
+-- | Generate a random bit vector using 'largeNum'.
genBitVec :: Gen BitVec
genBitVec = fmap fromIntegral largeNum
+-- | Return a random 'BinaryOperator'. This currently excludes 'BinDiv',
+-- 'BinMod' because they can take a long time to synthesis, and 'BinCEq',
+-- 'BinCNEq', because these are not synthesisable. 'BinPower' is also excluded
+-- because it can only be used in conjunction with base powers of 2 which is
+-- currently not enforced.
binOp :: Gen BinaryOperator
binOp = Hog.element
[ BinPlus
@@ -147,6 +204,7 @@ binOp = Hog.element
, BinASR
]
+-- | Generate a random 'UnaryOperator'.
unOp :: Gen UnaryOperator
unOp = Hog.element
[ UnPlus
@@ -162,6 +220,7 @@ unOp = Hog.element
, UnNxorInv
]
+-- | Generate a random 'ConstExpr' by using the current context of 'Parameter'.
constExprWithContext :: [Parameter] -> ProbExpr -> Hog.Size -> Gen ConstExpr
constExprWithContext ps prob size
| size == 0 = Hog.frequency
@@ -189,9 +248,13 @@ constExprWithContext ps prob size
| otherwise = constExprWithContext ps prob 0
where subexpr y = constExprWithContext ps prob $ size `div` y
+-- | The list of safe 'Expr', meaning that these will not recurse and will end
+-- the 'Expr' generation.
exprSafeList :: ProbExpr -> [(Int, Gen Expr)]
exprSafeList prob = [(prob ^. probExprNum, Number <$> genBitVec)]
+-- | List of 'Expr' that have the chance to recurse and will therefore not be
+-- used when the expression grows too large.
exprRecList :: ProbExpr -> (Hog.Size -> Gen Expr) -> [(Int, Gen Expr)]
exprRecList prob subexpr =
[ (prob ^. probExprNum, Number <$> genBitVec)
@@ -206,6 +269,8 @@ exprRecList prob subexpr =
, (prob ^. probExprUnsigned, Appl <$> pure "$unsigned" <*> subexpr 2)
]
+-- | Select a random port from a list of ports and generate a safe bit selection
+-- for that port.
rangeSelect :: [Parameter] -> [Port] -> Gen Expr
rangeSelect ps ports = do
p <- Hog.element ports
@@ -215,6 +280,8 @@ rangeSelect ps ports = do
return . RangeSelect (_portName p) $ Range (fromIntegral msb)
(fromIntegral lsb)
+-- | Generate a random expression from the 'Context' with a guarantee that it
+-- will terminate using the list of safe 'Expr'.
exprWithContext :: ProbExpr -> [Parameter] -> [Port] -> Hog.Size -> Gen Expr
exprWithContext prob ps [] n | n == 0 = Hog.frequency $ exprSafeList prob
| n > 0 = Hog.frequency $ exprRecList prob subexpr
@@ -234,11 +301,15 @@ exprWithContext prob ps l n
= exprWithContext prob ps l 0
where subexpr y = exprWithContext prob ps l $ n `div` y
+-- | Runs a 'StateGen' for a random number of times, limited by an 'Int' that is
+-- passed to it.
someI :: Int -> StateGen a -> StateGen [a]
someI m f = do
amount <- gen $ Hog.int (Hog.linear 1 m)
replicateM amount f
+-- | Make a new name with a prefix and the current nameCounter. The nameCounter
+-- is then increased so that the label is unique.
makeIdentifier :: T.Text -> StateGen Identifier
makeIdentifier prefix = do
context <- get
@@ -252,18 +323,26 @@ getPort' pt i c = case filter portId c of
[] -> newPort i pt
where portId (Port pt' _ _ i') = i == i' && pt == pt'
+-- | Makes a new 'Identifier' and then checks if the 'Port' already exists, if
+-- it does the existant 'Port' is returned, otherwise a new port is created with
+-- 'newPort'. This is used subsequently in all the functions to create a port,
+-- in case a port with the same name was already created. This could be because
+-- the generation is currently in the other branch of an if-statement.
nextPort :: PortType -> StateGen Port
nextPort pt = do
context <- get
ident <- makeIdentifier . T.toLower $ showT pt
getPort' pt ident (_variables context)
+-- | Creates a new port based on the current name counter and adds it to the
+-- current context.
newPort :: Identifier -> PortType -> StateGen Port
newPort ident pt = do
p <- gen $ Port pt <$> Hog.bool <*> range <*> pure ident
variables %= (p :)
return p
+-- | Generates an expression from variables that are currently in scope.
scopedExpr :: StateGen Expr
scopedExpr = do
context <- get
@@ -273,27 +352,22 @@ scopedExpr = do
. exprWithContext (_probExpr prob) (_parameters context)
$ _variables context
+-- | Generates a random continuous assignment and assigns it to a random wire
+-- that is created.
contAssign :: StateGen ContAssign
contAssign = do
expr <- scopedExpr
p <- nextPort Wire
return $ ContAssign (p ^. portName) expr
-lvalFromPort :: Port -> LVal
-lvalFromPort (Port _ _ _ i) = RegId i
-
-probability :: Config -> Probability
-probability c = c ^. configProbability
-
-askProbability :: StateGen Probability
-askProbability = lift $ asks probability
-
+-- | Generate a random assignment and assign it to a random 'Reg'.
assignment :: StateGen Assign
assignment = do
expr <- scopedExpr
lval <- lvalFromPort <$> nextPort Reg
return $ Assign lval Nothing expr
+-- | Generate a random 'Statement' safely, by also increasing the depth counter.
seqBlock :: StateGen Statement
seqBlock = do
stmntDepth -= 1
@@ -301,6 +375,10 @@ seqBlock = do
stmntDepth += 1
return tstat
+-- | Generate a random conditional 'Statement'. The nameCounter is reset between
+-- branches so that port names can be reused. This is safe because if a 'Port'
+-- is not reused, it is left at 0, as all the 'Reg' are initialised to 0 at the
+-- start.
conditional :: StateGen Statement
conditional = do
expr <- scopedExpr
@@ -313,6 +391,8 @@ conditional = do
nameCounter .= max nc' nc''
return $ CondStmnt expr (Just tstat) (Just fstat)
+-- | Generate a random for loop by creating a new variable name for the counter
+-- and then generating random statements in the body.
forLoop :: StateGen Statement
forLoop = do
num <- Hog.int (Hog.linear 0 20)
@@ -323,6 +403,7 @@ forLoop = do
<$> seqBlock
where varId v = Id (v ^. regId)
+-- | Choose a 'Statement' to generate.
statement :: StateGen Statement
statement = do
prob <- askProbability
@@ -336,6 +417,7 @@ statement = do
]
where onDepth c n = if c ^. stmntDepth > 0 then n else 0
+-- | Generate a sequential always block which is dependent on the clock.
alwaysSeq :: StateGen ModItem
alwaysSeq = Always . EventCtrl (EPosEdge "clk") . Just <$> seqBlock
@@ -346,7 +428,7 @@ resizePort :: [Parameter] -> Identifier -> Range -> [Port] -> [Port]
resizePort ps i ra = foldl' func []
where
func l p@(Port t _ ri i')
- | i' == i && calc ri < calc ra = trace (fmap toLower (show t) <> " " <> show (GenVerilog i) <> ": " <> (show $ calc ri) <> " to " <> (show $ calc ra)) $ (p & portSize .~ ra) : l
+ | i' == i && calc ri < calc ra = (p & portSize .~ ra) : l
| otherwise = p : l
calc = calcRange ps $ Just 64
diff --git a/src/VeriFuzz/Verilog/AST.hs b/src/VeriFuzz/Verilog/AST.hs
index e90d388..a85c365 100644
--- a/src/VeriFuzz/Verilog/AST.hs
+++ b/src/VeriFuzz/Verilog/AST.hs
@@ -10,16 +10,17 @@ Poratbility : POSIX
Defines the types to build a Verilog AST.
-}
-{-# LANGUAGE DeriveDataTypeable #-}
-{-# LANGUAGE DeriveFoldable #-}
-{-# LANGUAGE DeriveFunctor #-}
-{-# LANGUAGE DeriveTraversable #-}
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-{-# LANGUAGE MultiParamTypeClasses #-}
-{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE DeriveAnyClass #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE DeriveFoldable #-}
+{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE DeriveTraversable #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TypeFamilies #-}
module VeriFuzz.Verilog.AST
( -- * Top level types
@@ -139,25 +140,45 @@ module VeriFuzz.Verilog.AST
)
where
+import Control.DeepSeq (NFData)
import Control.Lens hiding ((<|))
import Data.Data
import Data.Data.Lens
import Data.Functor.Foldable.TH (makeBaseFunctor)
import Data.List.NonEmpty (NonEmpty (..), (<|))
import Data.String (IsString, fromString)
-import Data.Text (Text)
+import Data.Text (Text, pack)
import Data.Traversable (sequenceA)
+import GHC.Generics (Generic)
import VeriFuzz.Verilog.BitVec
-- | Identifier in Verilog. This is just a string of characters that can either
-- be lowercase and uppercase for now. This might change in the future though,
-- as Verilog supports many more characters in Identifiers.
newtype Identifier = Identifier { getIdentifier :: Text }
- deriving (Eq, Show, Ord, Data, IsString, Semigroup, Monoid)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
+
+instance IsString Identifier where
+ fromString = Identifier . pack
+
+instance Semigroup Identifier where
+ Identifier a <> Identifier b = Identifier $ a <> b
+
+instance Monoid Identifier where
+ mempty = Identifier mempty
-- | Verilog syntax for adding a delay, which is represented as @#num@.
newtype Delay = Delay { _getDelay :: Int }
- deriving (Eq, Show, Ord, Data, Num)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
+
+instance Num Delay where
+ Delay a + Delay b = Delay $ a + b
+ Delay a - Delay b = Delay $ a - b
+ Delay a * Delay b = Delay $ a * b
+ negate (Delay a) = Delay $ negate a
+ abs (Delay a) = Delay $ abs a
+ signum (Delay a) = Delay $ signum a
+ fromInteger = Delay . fromInteger
-- | Verilog syntax for an event, such as @\@x@, which is used for always blocks
data Event = EId {-# UNPACK #-} !Identifier
@@ -167,7 +188,7 @@ data Event = EId {-# UNPACK #-} !Identifier
| ENegEdge {-# UNPACK #-} !Identifier
| EOr !Event !Event
| EComb !Event !Event
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
instance Plated Event where
plate = uniplate
@@ -198,7 +219,7 @@ data BinaryOperator = BinPlus -- ^ @+@
| BinLSR -- ^ @>>@
| BinASL -- ^ @<<<@
| BinASR -- ^ @>>>@
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | Unary operators that are currently supported by the generator.
data UnaryOperator = UnPlus -- ^ @+@
@@ -212,7 +233,7 @@ data UnaryOperator = UnPlus -- ^ @+@
| UnXor -- ^ @^@
| UnNxor -- ^ @~^@
| UnNxorInv -- ^ @^~@
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | Verilog expression, which can either be a primary expression, unary
-- expression, binary operator expression or a conditional expression.
@@ -229,7 +250,7 @@ data Expr = Number {-# UNPACK #-} !BitVec
| Cond !Expr !Expr !Expr
| Appl !Identifier !Expr
| Str {-# UNPACK #-} !Text
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
instance Num Expr where
a + b = BinOp a BinPlus b
@@ -271,7 +292,7 @@ data ConstExpr = ConstNum { _constNum :: {-# UNPACK #-} !BitVec }
, _constFalse :: !ConstExpr
}
| ConstStr { _constStr :: {-# UNPACK #-} !Text }
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
constToExpr :: ConstExpr -> Expr
constToExpr (ConstNum a ) = Number a
@@ -320,7 +341,7 @@ instance Plated ConstExpr where
data Task = Task { _taskName :: {-# UNPACK #-} !Identifier
, _taskExpr :: [Expr]
- } deriving (Eq, Show, Ord, Data)
+ } deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | Type that represents the left hand side of an assignment, which can be a
-- concatenation such as in:
@@ -336,7 +357,7 @@ data LVal = RegId { _regId :: {-# UNPACK #-} !Identifier }
, _regSizeRange :: {-# UNPACK #-} !Range
}
| RegConcat { _regConc :: [Expr] }
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
instance IsString LVal where
fromString = RegId . fromString
@@ -345,13 +366,13 @@ instance IsString LVal where
data PortDir = PortIn -- ^ Input direction for port (@input@).
| PortOut -- ^ Output direction for port (@output@).
| PortInOut -- ^ Inout direction for port (@inout@).
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | Currently, only @wire@ and @reg@ are supported, as the other net types are
-- not that common and not a priority.
data PortType = Wire
| Reg
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | Range that can be associated with any port or left hand side. Contains the
-- msb and lsb bits as 'ConstExpr'. This means that they can be generated using
@@ -359,7 +380,7 @@ data PortType = Wire
data Range = Range { rangeMSB :: !ConstExpr
, rangeLSB :: !ConstExpr
}
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
instance Num Range where
(Range s1 a) + (Range s2 b) = Range (s1 + s2) $ a + b
@@ -382,7 +403,7 @@ data Port = Port { _portType :: !PortType
, _portSigned :: !Bool
, _portSize :: {-# UNPACK #-} !Range
, _portName :: {-# UNPACK #-} !Identifier
- } deriving (Eq, Show, Ord, Data)
+ } deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | This is currently a type because direct module declaration should also be
-- added:
@@ -394,16 +415,16 @@ data ModConn = ModConn { _modExpr :: !Expr }
| ModConnNamed { _modConnName :: {-# UNPACK #-} !Identifier
, _modExpr :: !Expr
}
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
data Assign = Assign { _assignReg :: !LVal
, _assignDelay :: !(Maybe Delay)
, _assignExpr :: !Expr
- } deriving (Eq, Show, Ord, Data)
+ } deriving (Eq, Show, Ord, Data, Generic, NFData)
data ContAssign = ContAssign { _contAssignNetLVal :: {-# UNPACK #-} !Identifier
, _contAssignExpr :: !Expr
- } deriving (Eq, Show, Ord, Data)
+ } deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | Statements in Verilog.
data Statement = TimeCtrl { _statDelay :: {-# UNPACK #-} !Delay
@@ -426,7 +447,7 @@ data Statement = TimeCtrl { _statDelay :: {-# UNPACK #-} !Delay
, _forIncr :: !Assign
, _forStmnt :: Statement
} -- ^ Loop bounds shall be statically computable for a for loop.
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
instance Plated Statement where
plate = uniplate
@@ -444,14 +465,14 @@ instance Monoid Statement where
data Parameter = Parameter { _paramIdent :: {-# UNPACK #-} !Identifier
, _paramValue :: ConstExpr
}
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | Local parameter that can be assigned anywhere using @localparam@. It cannot
-- be changed by initialising the module.
data LocalParam = LocalParam { _localParamIdent :: {-# UNPACK #-} !Identifier
, _localParamValue :: ConstExpr
}
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | Module item which is the body of the module expression.
data ModItem = ModCA { _modContAssign :: !ContAssign }
@@ -467,7 +488,7 @@ data ModItem = ModCA { _modContAssign :: !ContAssign }
}
| ParamDecl { _paramDecl :: NonEmpty Parameter }
| LocalParamDecl { _localParamDecl :: NonEmpty LocalParam }
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
-- | 'module' module_identifier [list_of_ports] ';' { module_item } 'end_module'
data ModDecl = ModDecl { _modId :: {-# UNPACK #-} !Identifier
@@ -476,7 +497,7 @@ data ModDecl = ModDecl { _modId :: {-# UNPACK #-} !Identifier
, _modItems :: ![ModItem]
, _modParams :: ![Parameter]
}
- deriving (Eq, Show, Ord, Data)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
traverseModConn :: (Applicative f) => (Expr -> f Expr) -> ModConn -> f ModConn
traverseModConn f (ModConn e ) = ModConn <$> f e
@@ -490,12 +511,18 @@ traverseModItem _ e = pure e
-- | The complete sourcetext for the Verilog module.
newtype Verilog = Verilog { getVerilog :: [ModDecl] }
- deriving (Eq, Show, Ord, Data, Semigroup, Monoid)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
+
+instance Semigroup Verilog where
+ Verilog a <> Verilog b = Verilog $ a <> b
+
+instance Monoid Verilog where
+ mempty = Verilog mempty
data SourceInfo = SourceInfo { _infoTop :: {-# UNPACK #-} !Text
, _infoSrc :: !Verilog
}
- deriving (Eq, Ord, Data, Show)
+ deriving (Eq, Show, Ord, Data, Generic, NFData)
$(makeLenses ''Expr)
$(makeLenses ''ConstExpr)
diff --git a/src/VeriFuzz/Verilog/BitVec.hs b/src/VeriFuzz/Verilog/BitVec.hs
index 80fa539..0cc9eb3 100644
--- a/src/VeriFuzz/Verilog/BitVec.hs
+++ b/src/VeriFuzz/Verilog/BitVec.hs
@@ -10,9 +10,11 @@ Portability : POSIX
Unsigned BitVec implementation.
-}
+{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
module VeriFuzz.Verilog.BitVec
@@ -23,16 +25,18 @@ module VeriFuzz.Verilog.BitVec
)
where
+import Control.DeepSeq (NFData)
import Data.Bits
import Data.Data
import Data.Ratio
+import GHC.Generics (Generic)
-- | Bit Vector that stores the bits in an arbitrary container together with the
-- size.
data BitVecF a = BitVec { width :: {-# UNPACK #-} !Int
, value :: !a
}
- deriving (Show, Eq, Ord, Data, Functor, Foldable, Traversable)
+ deriving (Show, Eq, Ord, Data, Functor, Foldable, Traversable, Generic, NFData)
-- | Specialisation of the above with Integer, so that infinitely large bit
-- vectors can be stored.
diff --git a/test/Benchmark.hs b/test/Benchmark.hs
index 5893b81..d0ea9cd 100644
--- a/test/Benchmark.hs
+++ b/test/Benchmark.hs
@@ -1,7 +1,15 @@
module Main where
-import Criterion (benchmark, nfAppIO)
-import VeriFuzz
+import Control.Lens ((&), (.~))
+import Criterion.Main (bench, bgroup, defaultMain, nfAppIO)
+import VeriFuzz (configProperty, defaultConfig, proceduralIO,
+ propSize, propStmntDepth)
main :: IO ()
-main = benchmark $ nfAppIO (proceduralIO "top") defaultConfig
+main = defaultMain
+ [ bgroup "generation"
+ [ bench "default" $ nfAppIO (proceduralIO "top") defaultConfig
+ , bench "depth" . nfAppIO (proceduralIO "top") $ defaultConfig & configProperty . propStmntDepth .~ 10
+ , bench "size" . nfAppIO (proceduralIO "top") $ defaultConfig & configProperty . propSize .~ 40
+ ]
+ ]
diff --git a/verifuzz.cabal b/verifuzz.cabal
index 49e3f68..6d15d45 100644
--- a/verifuzz.cabal
+++ b/verifuzz.cabal
@@ -96,6 +96,7 @@ library
, blaze-html >=0.9.0.1 && <0.10
, statistics >=0.14.0.2 && <0.16
, vector >=0.12.0.1 && <0.13
+ , unordered-containers >=0.2.10 && <0.3
default-extensions: OverloadedStrings
executable verifuzz
@@ -107,6 +108,17 @@ executable verifuzz
, verifuzz
default-extensions: OverloadedStrings
+benchmark benchmark
+ default-language: Haskell2010
+ type: exitcode-stdio-1.0
+ hs-source-dirs: test
+ main-is: Benchmark.hs
+ build-depends: base >=4 && <5
+ , verifuzz
+ , criterion >=1.5.5 && <1.6
+ , lens >=4.16.1 && <4.18
+ default-extensions: OverloadedStrings
+
test-suite test
default-language: Haskell2010
type: exitcode-stdio-1.0