verismith-1.1.0: Random verilog generation and simulator testing.
Copyright(c) 2018-2022 Yann Herklotz
LicenseGPL-3
Maintaineryann [at] yannherklotz [dot] com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Verismith.Verilog.Mutate

Description

Functions to mutate the Verilog AST from Verismith.Verilog.AST to generate more random patterns, such as nesting wires instead of creating new ones.

Synopsis

Documentation

class Mutate a where Source #

Methods

mutExpr :: (Expr -> Expr) -> a -> a Source #

Instances

Instances details
Mutate Assign Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Assign -> Assign Source #

Mutate BinaryOperator Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Mutate ConstExpr Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> ConstExpr -> ConstExpr Source #

Mutate ContAssign Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Mutate Delay Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Delay -> Delay Source #

Mutate Event Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Event -> Event Source #

Mutate Expr Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Expr -> Expr Source #

Mutate Identifier Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Mutate LVal Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> LVal -> LVal Source #

Mutate LocalParam Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Mutate ModConn Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> ModConn -> ModConn Source #

Mutate Parameter Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Parameter -> Parameter Source #

Mutate Port Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Port -> Port Source #

Mutate PortDir Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> PortDir -> PortDir Source #

Mutate PortType Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> PortType -> PortType Source #

Mutate Range Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Range -> Range Source #

Mutate Task Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Task -> Task Source #

Mutate UnaryOperator Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Mutate (CasePair ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> CasePair ann -> CasePair ann Source #

Mutate (ModDecl ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> ModDecl ann -> ModDecl ann Source #

Mutate (ModItem ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> ModItem ann -> ModItem ann Source #

Mutate (SourceInfo ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> SourceInfo ann -> SourceInfo ann Source #

Mutate (Statement ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Statement ann -> Statement ann Source #

Mutate (Verilog ann) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Verilog ann -> Verilog ann Source #

Mutate a => Mutate (GenVerilog a) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> GenVerilog a -> GenVerilog a Source #

Mutate a => Mutate (Maybe a) Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> Maybe a -> Maybe a Source #

Mutate a => Mutate [a] Source # 
Instance details

Defined in Verismith.Verilog.Mutate

Methods

mutExpr :: (Expr -> Expr) -> [a] -> [a] Source #

inPort :: Identifier -> ModDecl ann -> Bool Source #

Return if the Identifier is in a '(ModDecl ann)'.

findAssign :: Identifier -> [ModItem ann] -> Maybe Expr Source #

Find the last assignment of a specific wire/reg to an expression, and returns that expression.

idTrans :: Identifier -> Expr -> Expr -> Expr Source #

Transforms an expression by replacing an Identifier with an expression. This is used inside transformOf and traverseExpr to replace the Identifier recursively.

replace :: Identifier -> Expr -> Expr -> Expr Source #

Replaces the identifier recursively in an expression.

nestId :: Identifier -> ModDecl ann -> ModDecl ann Source #

Nest expressions for a specific Identifier. If the Identifier is not found, the AST is not changed.

This could be improved by instead of only using the last assignment to the wire that one finds, to use the assignment to the wire before the current expression. This would require a different approach though.

nestSource :: Identifier -> Verilog ann -> Verilog ann Source #

Replaces an identifier by a expression in all the module declaration.

nestUpTo :: Int -> Verilog ann -> Verilog ann Source #

Nest variables in the format w[0-9]* up to a certain number.

instantiateMod :: ModDecl ann -> ModDecl ann -> ModDecl ann Source #

Add a Module Instantiation using ModInst from the first module passed to it to the body of the second module. It first has to make all the inputs into reg.

>>> render $ instantiateMod m main
module main;
  wire [(3'h4):(1'h0)] y;
  reg [(3'h4):(1'h0)] x;
  m m1(y, x);
endmodule


instantiateMod_ :: ModDecl ann -> ModItem ann Source #

Instantiate without adding wire declarations. It also does not count the current instantiations of the same module.

>>> GenVerilog $ instantiateMod_ m
m m(y, x);

instantiateModSpec_ :: Bool -> Text -> ModDecl ann -> ModItem ann Source #

Instantiate without adding wire declarations. It also does not count the current instantiations of the same module.

>>> GenVerilog $ instantiateModSpec_ "_" m
m m(.y(y), .x(x));

initMod :: ModDecl ann -> ModDecl ann Source #

Initialise all the inputs and outputs to a module.

>>> GenVerilog $ initMod m
module m(y, x);
  output wire [(3'h4):(1'h0)] y;
  input wire [(3'h4):(1'h0)] x;
endmodule


makeIdFrom :: Show a => a -> Identifier -> Identifier Source #

Make an Identifier from and existing Identifier and an object with a Show instance to make it unique.

makeTop :: Bool -> Int -> ModDecl ann -> ModDecl ann Source #

Make top level module for equivalence verification. Also takes in how many modules to instantiate.

makeTopAssert :: ModDecl ann -> ModDecl ann Source #

Make a top module with an assert that requires y_1 to always be equal to y_2, which can then be proven using a formal verification tool.

simplify :: Expr -> Expr Source #

Simplify an Expr by using constants to remove BinaryOperator and simplify expressions. To make this work effectively, it should be run until no more changes were made to the expression.

>>> GenVerilog . simplify $ (Id "x") + 0
x
>>> GenVerilog . simplify $ (Id "y") + (Id "x")
(y + x)

removeId :: [Identifier] -> Expr -> Expr Source #

Remove all Identifier that do not appeare in the input list from an Expr. The identifier will be replaced by 1'b0, which can then later be simplified further.

>>> GenVerilog . removeId ["x"] $ Id "x" + Id "y"
(x + (1'h0))

combineAssigns :: Port -> [ModItem ann] -> [ModItem ann] Source #

declareMod :: [Port] -> ModDecl ann -> ModDecl ann Source #

Provide declarations for all the ports that are passed to it. If they are registers, it should assign them to 0.