verismith-0.6.0.2: Random verilog generation and simulator testing.

Copyright(c) 2019 Yann Herklotz
LicenseGPL-3
Maintaineryann [at] yannherklotz [dot] com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Verismith.Generate

Contents

Description

Various useful generators.

Synopsis

Generation methods

procedural :: Text -> Config -> Gen Verilog Source #

Procedural generation method for random Verilog. Uses internal Reader and State to keep track of the current Verilog code structure.

proceduralIO :: Text -> Config -> IO Verilog Source #

Samples the Gen directly to generate random Verilog using the Text as the name of the main module and the configuration Config to influence the generation.

proceduralSrc :: Text -> Config -> Gen SourceInfo Source #

Given a Text and a Config will generate a SourceInfo which has the top module set to the right name.

proceduralSrcIO :: Text -> Config -> IO SourceInfo Source #

Sampled and wrapped into a SourceInfo with the given top module name.

Generate Functions

largeNum :: MonadGen m => m Int Source #

Generates a random large number, which can also be negative.

wireSize :: MonadGen m => m Int Source #

Generates a random size for a wire so that it is not too small and not too large.

range :: MonadGen m => m Range Source #

Generates a random range by using the wireSize and 0 as the lower bound.

genBitVec :: MonadGen m => m BitVec Source #

Generate a random bit vector using largeNum.

binOp :: MonadGen m => m BinaryOperator Source #

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.

unOp :: MonadGen m => m UnaryOperator Source #

Generate a random UnaryOperator.

constExprWithContext :: MonadGen m => [Parameter] -> ProbExpr -> Size -> m ConstExpr Source #

Generate a random ConstExpr by using the current context of Parameter.

exprSafeList :: MonadGen m => ProbExpr -> [(Int, m Expr)] Source #

The list of safe Expr, meaning that these will not recurse and will end the Expr generation.

exprRecList :: MonadGen m => ProbExpr -> (Size -> m Expr) -> [(Int, m Expr)] Source #

List of Expr that have the chance to recurse and will therefore not be used when the expression grows too large.

exprWithContext :: MonadGen m => ProbExpr -> [Parameter] -> [Port] -> Size -> m Expr Source #

Generate a random expression from the Context with a guarantee that it will terminate using the list of safe Expr.

makeIdentifier :: Text -> StateGen Identifier Source #

Make a new name with a prefix and the current nameCounter. The nameCounter is then increased so that the label is unique.

nextPort :: Maybe Text -> PortType -> StateGen Port Source #

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.

newPort :: Identifier -> PortType -> StateGen Port Source #

Creates a new port based on the current name counter and adds it to the current context.

scopedExpr :: StateGen Expr Source #

Generates an expression from variables that are currently in scope.

contAssign :: StateGen ContAssign Source #

Generates a random continuous assignment and assigns it to a random wire that is created.

lvalFromPort :: Port -> LVal Source #

Converts a Port to an LVal by only keeping the Identifier of the Port.

assignment :: StateGen Assign Source #

Generate a random assignment and assign it to a random Reg.

seqBlock :: StateGen Statement Source #

Generate a random Statement safely, by also increasing the depth counter.

conditional :: StateGen Statement Source #

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.

forLoop :: StateGen Statement Source #

Generate a random for loop by creating a new variable name for the counter and then generating random statements in the body.

statement :: StateGen Statement Source #

Choose a Statement to generate.

alwaysSeq :: StateGen ModItem Source #

Generate a sequential always block which is dependent on the clock.

instantiate :: ModDecl -> StateGen ModItem Source #

Instantiate a module, where the outputs are new nets that are created, and the inputs are taken from existing ports in the context.

1 is subtracted from the inputs for the length because the clock is not counted and is assumed to be there, this should be made nicer by filtering out the clock instead. I think that in general there should be a special representation for the clock.

modInst :: StateGen ModItem Source #

Generates a module instance by also generating a new module if there are not enough modules currently in the context. It keeps generating new modules for every instance and for every level until either the deepest level is achieved, or the maximum number of modules are reached.

If the maximum number of levels are reached, it will always pick an instance from the current context. The problem with this approach is that at the end there may be many more than the max amount of modules, as the modules are always set to empty when entering a new level. This is to fix recursive definitions of modules, which are not defined.

One way to fix that is to also decrement the max modules for every level, depending on how many modules have already been generated. This would mean there would be moments when the module cannot generate a new instance but also not take a module from the current context. A fix for that may be to have a default definition of a simple module that is used instead.

Another different way to handle this would be to have a probability of taking a module from a context or generating a new one.

modItem :: StateGen ModItem Source #

Generate a random module item.

constExpr :: StateGen ConstExpr Source #

Generate a random ConstExpr by using the current context of Parameters.

parameter :: StateGen Parameter Source #

Generate a random Parameter and assign it to a constant expression which it will be initialised to. The assumption is that this constant expression should always be able to be evaluated with the current context of parameters.

moduleDef :: Maybe Identifier -> StateGen ModDecl Source #

Generates a module definition randomly. It always has one output port which is set to y. The size of y is the total combination of all the locally defined wires, so that it correctly reflects the internal state of the module.

Helpers

someI :: Int -> StateGen a -> StateGen [a] Source #

Runs a StateGen for a random number of times, limited by an Int that is passed to it.

probability :: Config -> Probability Source #

Returns the probability from the configuration.

askProbability :: StateGen Probability Source #

Gets the current probabilities from the State.

resizePort :: [Parameter] -> Identifier -> Range -> [Port] -> [Port] Source #

Should resize a port that connects to a module port if the latter is larger. This should not cause any problems if the same net is used as input multiple times, and is resized multiple times, as it should only get larger.

moduleName :: Maybe Identifier -> StateGen Identifier Source #

Either return the Identifier that was passed to it, or generate a new Identifier based on the current nameCounter.

evalRange :: [Parameter] -> Int -> Range -> Range Source #

Evaluate a range to an integer, and cast it back to a range.

calcRange :: [Parameter] -> Maybe Int -> Range -> Int Source #

Calculate a range to an int by maybe resizing the ranges to a value.