aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorYann Herklotz <ymherklotz@gmail.com>2018-12-29 01:56:39 +0100
committerYann Herklotz <ymherklotz@gmail.com>2018-12-29 01:56:39 +0100
commit5db743f5343e874dfeab2e4f81ee98550ce8ef49 (patch)
tree4b54ac492f1384bfd39b2346ce92d42f2c40f1cd /src
parentf0cc5bb8865b039b18bdc89e81df9bad72e0bdb5 (diff)
downloadverismith-5db743f5343e874dfeab2e4f81ee98550ce8ef49.tar.gz
verismith-5db743f5343e874dfeab2e4f81ee98550ce8ef49.zip
Changes to the API
Diffstat (limited to 'src')
-rw-r--r--src/Test/VeriFuzz/Graph/ASTGen.hs35
-rw-r--r--src/Test/VeriFuzz/Helpers.hs12
-rw-r--r--src/Test/VeriFuzz/Verilog/AST.hs27
-rw-r--r--src/Test/VeriFuzz/Verilog/CodeGen.hs23
-rw-r--r--src/Test/VeriFuzz/Verilog/Mutate.hs6
5 files changed, 60 insertions, 43 deletions
diff --git a/src/Test/VeriFuzz/Graph/ASTGen.hs b/src/Test/VeriFuzz/Graph/ASTGen.hs
index 748824f..28dc32a 100644
--- a/src/Test/VeriFuzz/Graph/ASTGen.hs
+++ b/src/Test/VeriFuzz/Graph/ASTGen.hs
@@ -12,15 +12,16 @@ Generates the AST from the graph directly.
module Test.VeriFuzz.Graph.ASTGen where
-import Data.Graph.Inductive (LNode, Node)
-import qualified Data.Graph.Inductive as G
-import Data.Maybe (catMaybes)
-import qualified Data.Text as T
+import Data.Graph.Inductive (LNode, Node)
+import qualified Data.Graph.Inductive as G
+import Data.Maybe (catMaybes)
+import qualified Data.Text as T
import Test.VeriFuzz.Circuit
import Test.VeriFuzz.Internal.Gen
+import Test.VeriFuzz.Internal.Shared
import Test.VeriFuzz.Verilog.AST
--- | Converts a 'Node' to an 'Identifier'.
+-- | Converts a 'CNode' to an 'Identifier'.
frNode :: Node -> Identifier
frNode = Identifier . fromNode
@@ -31,14 +32,19 @@ fromGate And = BinAnd
fromGate Or = BinOr
fromGate Xor = BinXor
-genPortsAST :: Circuit -> [Port]
-genPortsAST c =
- (port Input . frNode <$> inp) ++ (port Output . frNode <$> out)
+inputsC :: Circuit -> [Node]
+inputsC c =
+ inputs (getCircuit c)
+
+outputsC :: Circuit -> [Node]
+outputsC c =
+ outputs (getCircuit c)
+
+genPortsAST :: (Circuit -> [Node]) -> Circuit -> [Port]
+genPortsAST f c =
+ (port . frNode <$> f c)
where
- inp = inputs graph
- out = outputs graph
- graph = getCircuit c
- port x = Port (Just x) Nothing
+ port = Port $ PortNet Wire
-- | Generates the nested expression AST, so that it can then generate the
-- assignment expressions.
@@ -67,10 +73,11 @@ genAssignAST c = catMaybes $ genContAssignAST c <$> nodes
nodes = G.labNodes gr
genModuleDeclAST :: Circuit -> ModDecl
-genModuleDeclAST c = ModDecl id ports items
+genModuleDeclAST c = ModDecl id Nothing ports items
where
id = Identifier "gen_module"
- ports = genPortsAST c
+ ports = genPortsAST inputsC c
+ outPut = safe head $ genPortsAST inputsC c
items = genAssignAST c
generateAST :: Circuit -> VerilogSrc
diff --git a/src/Test/VeriFuzz/Helpers.hs b/src/Test/VeriFuzz/Helpers.hs
index 6632938..6643683 100644
--- a/src/Test/VeriFuzz/Helpers.hs
+++ b/src/Test/VeriFuzz/Helpers.hs
@@ -18,10 +18,10 @@ import qualified Data.Text
import Test.VeriFuzz.Verilog.AST
regDecl :: Text -> ModItem
-regDecl = Decl . Port Nothing (Just $ Reg False) . Identifier
+regDecl = Decl . Port (Reg False) . Identifier
wireDecl :: Text -> ModItem
-wireDecl = Decl . Port Nothing (Just $ PortNet Wire) . Identifier
+wireDecl = Decl . Port (PortNet Wire) . Identifier
modConn :: Text -> ModConn
modConn = ModConn . PrimExpr . PrimId . Identifier
@@ -32,22 +32,22 @@ numExpr = ((PrimExpr . PrimNum) .) . Number
-- | Create an empty module.
emptyMod :: ModDecl
-emptyMod = ModDecl (Identifier "") [] []
+emptyMod = ModDecl "" Nothing [] []
-- | Set a module name for a module declaration.
setModName :: Text -> ModDecl -> ModDecl
setModName str = moduleId .~ Identifier str
--- | Add a port to the module declaration.
+-- | Add a input port to the module declaration.
addModPort :: Port -> ModDecl -> ModDecl
-addModPort port = modPorts %~ (:) port
+addModPort port = modInPorts %~ (:) port
addDescription :: Description -> VerilogSrc -> VerilogSrc
addDescription desc = getVerilogSrc %~ (:) desc
testBench :: ModDecl
testBench =
- ModDecl "main" []
+ ModDecl "main" Nothing []
[ regDecl "a"
, regDecl "b"
, wireDecl "c"
diff --git a/src/Test/VeriFuzz/Verilog/AST.hs b/src/Test/VeriFuzz/Verilog/AST.hs
index d5dba97..9f406dc 100644
--- a/src/Test/VeriFuzz/Verilog/AST.hs
+++ b/src/Test/VeriFuzz/Verilog/AST.hs
@@ -5,7 +5,7 @@ Copyright : (c) 2018-2019, Yann Herklotz Grave
License : BSD-3
Maintainer : ymherklotz [at] gmail [dot] com
Stability : experimental
-Portability : POSIX
+Poratbility : POSIX
Defines the types to build a Verilog AST.
-}
@@ -134,9 +134,9 @@ newtype ConstExpr = ConstExpr { _constNum :: Int }
deriving (Show, Eq, Ord)
-- | Different port direction that are supported in Verilog.
-data PortDir = Input -- ^ Input direction for port (@input@).
- | Output -- ^ Output direction for port (@output@).
- | InOut -- ^ Inout direction for port (@inout@).
+data PortDir = PortIn -- ^ Input direction for port (@input@).
+ | PortOut -- ^ Output direction for port (@output@).
+ | PortInOut -- ^ Inout direction for port (@inout@).
deriving (Show, Eq, Ord)
data PortType = PortNet Net
@@ -144,8 +144,7 @@ data PortType = PortNet Net
deriving (Show, Eq, Ord)
-- | Port declaration.
-data Port = Port { _portDir :: Maybe PortDir
- , _portType :: Maybe PortType
+data Port = Port { _portType :: PortType
, _portName :: Identifier
} deriving (Show, Eq, Ord)
@@ -193,7 +192,8 @@ data ModItem = ModCA ContAssign
-- | 'module' module_identifier [list_of_ports] ';' { module_item } 'end_module'
data ModDecl = ModDecl { _moduleId :: Identifier
- , _modPorts :: [Port]
+ , _modOutPort :: Maybe Port
+ , _modInPorts :: [Port]
, _moduleItems :: [ModItem]
} deriving (Show, Eq, Ord)
@@ -249,8 +249,8 @@ statement n
modPortGen :: QC.Gen Port
modPortGen = QC.oneof
- [ Port (Just Input) Nothing <$> QC.arbitrary
- , Port (Just Output) <$> (Just . Reg <$> QC.arbitrary) <*> QC.arbitrary
+ [ Port (PortNet Wire) <$> QC.arbitrary
+ , Port <$> (Reg <$> QC.arbitrary) <*> QC.arbitrary
]
instance QC.Arbitrary Text where
@@ -313,13 +313,13 @@ instance QC.Arbitrary Primary where
arbitrary = PrimNum <$> QC.arbitrary
instance QC.Arbitrary PortDir where
- arbitrary = QC.elements [Input, Output, InOut]
+ arbitrary = QC.elements [PortIn, PortOut, PortInOut]
instance QC.Arbitrary PortType where
arbitrary = QC.oneof [PortNet <$> QC.arbitrary, Reg <$> QC.arbitrary]
instance QC.Arbitrary Port where
- arbitrary = Port Nothing <$> QC.arbitrary <*> QC.arbitrary
+ arbitrary = Port <$> QC.arbitrary <*> QC.arbitrary
instance QC.Arbitrary Delay where
arbitrary = Delay <$> QC.suchThat QC.arbitrary (\x -> x > 0)
@@ -331,7 +331,7 @@ instance QC.Arbitrary ModConn where
arbitrary = ModConn <$> QC.arbitrary
instance QC.Arbitrary ConstExpr where
- arbitrary = ConstExpr <$> QC.arbitrary
+ arbitrary = ConstExpr <$> QC.suchThat QC.arbitrary (\x -> x > 0)
instance QC.Arbitrary RegLVal where
arbitrary = QC.oneof [ RegId <$> QC.arbitrary
@@ -363,7 +363,8 @@ instance QC.Arbitrary ModItem where
]
instance QC.Arbitrary ModDecl where
- arbitrary = ModDecl <$> QC.arbitrary <*> QC.listOf1 modPortGen <*> QC.arbitrary
+ arbitrary = ModDecl <$> QC.arbitrary <*> QC.arbitrary
+ <*> QC.listOf1 modPortGen <*> QC.arbitrary
instance QC.Arbitrary Description where
arbitrary = Description <$> QC.arbitrary
diff --git a/src/Test/VeriFuzz/Verilog/CodeGen.hs b/src/Test/VeriFuzz/Verilog/CodeGen.hs
index ecc315f..e1114d2 100644
--- a/src/Test/VeriFuzz/Verilog/CodeGen.hs
+++ b/src/Test/VeriFuzz/Verilog/CodeGen.hs
@@ -14,7 +14,7 @@ This module generates the code from the Verilog AST defined in
module Test.VeriFuzz.Verilog.CodeGen where
import Control.Lens
-import Data.Maybe (fromMaybe)
+import Data.Maybe (fromMaybe, isNothing)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as T
@@ -46,24 +46,29 @@ genModuleDecl mod =
<> "endmodule\n"
where
ports
- | null $ mod ^. modPorts = ""
- | otherwise = "(\n" <> (sep ",\n" $ genPort <$> mod ^. modPorts) <> "\n)"
+ | noIn && noOut = ""
+ | otherwise = "(" <> out <> (sep ", " $ genModPort <$> mod ^. modInPorts) <> ")"
modItems = fromList $ genModuleItem <$> mod ^. moduleItems
+ noOut = isNothing $ mod ^. modOutPort
+ noIn = null $ mod ^. modInPorts
+ out = fromMaybe "" . safe head $ mod ^.. modOutPort . _Just . portName . getIdentifier
+
+genModPort :: Port -> Text
+genModPort port = port ^. portName . getIdentifier
-- | Generate the 'Port' description.
genPort :: Port -> Text
genPort port =
- dir <> t <> name
+ t <> name
where
- dir = fromMaybe "" $ (<>" ") . genPortDir <$> port ^. portDir
- t = fromMaybe "wire " $ (<>" ") . genPortType <$> port ^. portType
+ t = (<>" ") . genPortType $ port ^. portType
name = port ^. portName . getIdentifier
-- | Convert the 'PortDir' type to 'Text'.
genPortDir :: PortDir -> Text
-genPortDir Input = "input"
-genPortDir Output = "output"
-genPortDir InOut = "inout"
+genPortDir PortIn = "input"
+genPortDir PortOut = "output"
+genPortDir PortInOut = "inout"
-- | Generate a 'ModItem'.
genModuleItem :: ModItem -> Text
diff --git a/src/Test/VeriFuzz/Verilog/Mutate.hs b/src/Test/VeriFuzz/Verilog/Mutate.hs
index 66e56a1..6731b65 100644
--- a/src/Test/VeriFuzz/Verilog/Mutate.hs
+++ b/src/Test/VeriFuzz/Verilog/Mutate.hs
@@ -21,7 +21,11 @@ import Test.VeriFuzz.Verilog.AST
-- | Return if the 'Identifier' is in a 'ModDecl'.
inPort :: Identifier -> ModDecl -> Bool
-inPort id mod = any (\a -> a ^. portName == id) $ mod ^. modPorts
+inPort id mod = inInput || inOutput
+ where
+ inInput = any (\a -> a ^. portName == id) $ mod ^. modInPorts
+ inOutput = fromMaybe False . safe head $ (==id) <$>
+ mod ^.. modOutPort . _Just . portName
-- | Find the last assignment of a specific wire/reg to an expression, and
-- returns that expression.