aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorYann Herklotz <ymherklotz@gmail.com>2018-12-25 13:20:57 +0100
committerYann Herklotz <ymherklotz@gmail.com>2018-12-25 13:20:57 +0100
commitffd032f74a8eed1c47a93d7ce619734580e1ae61 (patch)
treeba09ebf36da069e162502a664bb0b643cef1a8bb /src
parent1d070b34a4e6f4a52abfe052bf49f589bd34d1b5 (diff)
downloadverismith-ffd032f74a8eed1c47a93d7ce619734580e1ae61.tar.gz
verismith-ffd032f74a8eed1c47a93d7ce619734580e1ae61.zip
Add Helpers.hs
Diffstat (limited to 'src')
-rw-r--r--src/Test/VeriFuzz/Helpers.hs75
1 files changed, 75 insertions, 0 deletions
diff --git a/src/Test/VeriFuzz/Helpers.hs b/src/Test/VeriFuzz/Helpers.hs
new file mode 100644
index 0000000..ca5505c
--- /dev/null
+++ b/src/Test/VeriFuzz/Helpers.hs
@@ -0,0 +1,75 @@
+{-|
+Module : Test.VeriFuzz.Default
+Description : Defaults and common functions.
+Copyright : (c) Yann Herklotz Grave 2018
+License : GPL-3
+Maintainer : ymherklotz@gmail.com
+Stability : experimental
+Portability : POSIX
+
+Defaults and common functions.
+-}
+
+{-# LANGUAGE OverloadedStrings #-}
+
+module Test.VeriFuzz.Helpers where
+
+import Control.Lens
+import Data.Text (Text)
+import qualified Data.Text
+import Test.VeriFuzz.VerilogAST
+
+regDecl :: Text -> ModItem
+regDecl = Decl . Port Nothing (Just $ Reg False) . Identifier
+
+wireDecl :: Text -> ModItem
+wireDecl = Decl . Port Nothing (Just $ PortNet Wire) . Identifier
+
+modConn :: Text -> ModConn
+modConn = ModConn . PrimExpr . PrimId . Identifier
+
+-- | Create a number expression which will be stored in a primary expression.
+numExpr :: Int -> Int -> Expression
+numExpr = ((PrimExpr . PrimNum) .) . Number
+
+-- | Create an empty module.
+emptyMod :: ModDecl
+emptyMod = ModDecl (Identifier "") [] []
+
+-- | Set a module name for a module declaration.
+setModName :: Text -> ModDecl -> ModDecl
+setModName str = moduleId .~ Identifier str
+
+-- | Add a port to the module declaration.
+addModPort :: Port -> ModDecl -> ModDecl
+addModPort port = modPorts %~ (:) port
+
+addDescription :: Description -> SourceText -> SourceText
+addDescription desc = getSourceText %~ (:) desc
+
+testBench :: ModDecl
+testBench =
+ ModDecl "main" []
+ [ regDecl "a"
+ , regDecl "b"
+ , wireDecl "c"
+ , ModInst "and" "and_gate"
+ [ modConn "c"
+ , modConn "a"
+ , modConn "b"
+ ]
+ , Initial $ SeqBlock
+ [ BlockAssign . Assign (RegId "a") Nothing . PrimExpr . PrimNum $ Number 1 1
+ , BlockAssign . Assign (RegId "b") Nothing . PrimExpr . PrimNum $ Number 1 1
+ -- , TimeCtrl (Delay 1) . Just . SysTaskEnable $ Task "display"
+ -- [ ExprStr "%d & %d = %d"
+ -- , PrimExpr $ PrimId "a"
+ -- , PrimExpr $ PrimId "b"
+ -- , PrimExpr $ PrimId "c"
+ -- ]
+ -- , SysTaskEnable $ Task "finish" []
+ ]
+ ]
+
+addTestBench :: SourceText -> SourceText
+addTestBench = addDescription $ Description testBench