Copyright | (c) 2018-2019 Yann Herklotz |
---|---|
License | BSD-3 |
Maintainer | yann [at] yannherklotz [dot] com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
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
- class Mutate a where
- inPort :: Identifier -> ModDecl -> Bool
- findAssign :: Identifier -> [ModItem] -> Maybe Expr
- idTrans :: Identifier -> Expr -> Expr -> Expr
- replace :: Identifier -> Expr -> Expr -> Expr
- nestId :: Identifier -> ModDecl -> ModDecl
- nestSource :: Identifier -> Verilog -> Verilog
- nestUpTo :: Int -> Verilog -> Verilog
- allVars :: ModDecl -> [Identifier]
- instantiateMod :: ModDecl -> ModDecl -> ModDecl
- instantiateMod_ :: ModDecl -> ModItem
- instantiateModSpec_ :: Text -> ModDecl -> ModItem
- filterChar :: Text -> [Identifier] -> [Identifier]
- initMod :: ModDecl -> ModDecl
- makeIdFrom :: Show a => a -> Identifier -> Identifier
- makeTop :: Int -> ModDecl -> ModDecl
- makeTopAssert :: ModDecl -> ModDecl
- simplify :: Expr -> Expr
- removeId :: [Identifier] -> Expr -> Expr
- combineAssigns :: Port -> [ModItem] -> [ModItem]
- combineAssigns_ :: Bool -> Port -> [Port] -> ModItem
- declareMod :: [Port] -> ModDecl -> ModDecl
- fromPort :: Port -> Identifier
Documentation
Instances
inPort :: Identifier -> ModDecl -> Bool Source #
Return if the Identifier
is in a ModDecl
.
findAssign :: Identifier -> [ModItem] -> 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 -> ModDecl 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 -> Verilog Source #
Replaces an identifier by a expression in all the module declaration.
nestUpTo :: Int -> Verilog -> Verilog Source #
Nest variables in the format w[0-9]*
up to a certain number.
allVars :: ModDecl -> [Identifier] Source #
instantiateMod :: ModDecl -> ModDecl -> ModDecl 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 -> ModItem 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_ :: Text -> ModDecl -> ModItem 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));
filterChar :: Text -> [Identifier] -> [Identifier] Source #
initMod :: ModDecl -> ModDecl 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 :: Int -> ModDecl -> ModDecl Source #
Make top level module for equivalence verification. Also takes in how many modules to instantiate.
makeTopAssert :: ModDecl -> ModDecl 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))
declareMod :: [Port] -> ModDecl -> ModDecl Source #
Provide declarations for all the ports that are passed to it. If they are registers, it should assign them to 0.
fromPort :: Port -> Identifier Source #