aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorYann Herklotz Grave <git@yannherklotzgrave.com>2019-02-16 14:28:30 +0000
committerYann Herklotz Grave <git@yannherklotzgrave.com>2019-02-16 14:28:30 +0000
commitf28188fc54d187b501b861d43592702bc7e460ec (patch)
treec1d898d080dcfa44a5461218a047d04883076a23 /src
parenta83b3b40f683400914d0f3ae23bd9e69e6e0fd96 (diff)
downloadverismith-f28188fc54d187b501b861d43592702bc7e460ec.tar.gz
verismith-f28188fc54d187b501b861d43592702bc7e460ec.zip
Add export lists
Diffstat (limited to 'src')
-rw-r--r--src/VeriFuzz/ASTGen.hs7
-rw-r--r--src/VeriFuzz/Circuit.hs7
-rw-r--r--src/VeriFuzz/CodeGen.hs32
-rw-r--r--src/VeriFuzz/Internal.hs12
-rw-r--r--src/VeriFuzz/Mutate.hs7
5 files changed, 41 insertions, 24 deletions
diff --git a/src/VeriFuzz/ASTGen.hs b/src/VeriFuzz/ASTGen.hs
index d113bbb..6bac157 100644
--- a/src/VeriFuzz/ASTGen.hs
+++ b/src/VeriFuzz/ASTGen.hs
@@ -10,7 +10,9 @@ Portability : POSIX
Generates the AST from the graph directly.
-}
-module VeriFuzz.ASTGen where
+module VeriFuzz.ASTGen
+ ( generateAST
+ ) where
import Control.Lens ((^..))
import Data.Foldable (fold)
@@ -35,9 +37,6 @@ fromGate Xor = BinXor
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 port = Port Wire 4
diff --git a/src/VeriFuzz/Circuit.hs b/src/VeriFuzz/Circuit.hs
index 7958f6a..7091fb3 100644
--- a/src/VeriFuzz/Circuit.hs
+++ b/src/VeriFuzz/Circuit.hs
@@ -10,7 +10,12 @@ Portability : POSIX
Definition of the circuit graph.
-}
-module VeriFuzz.Circuit where
+module VeriFuzz.Circuit
+ ( -- * Circuit
+ Gate(..)
+ , Circuit(..)
+ , CNode(..)
+ ) where
import Data.Graph.Inductive (Gr, LNode)
import System.Random
diff --git a/src/VeriFuzz/CodeGen.hs b/src/VeriFuzz/CodeGen.hs
index ea3159d..f35eff7 100644
--- a/src/VeriFuzz/CodeGen.hs
+++ b/src/VeriFuzz/CodeGen.hs
@@ -13,16 +13,22 @@ This module generates the code from the Verilog AST defined in
{-# LANGUAGE FlexibleInstances #-}
-module VeriFuzz.CodeGen where
-
-import Control.Lens (view, (^.))
-import Data.Foldable (fold)
-import Data.Text (Text)
-import qualified Data.Text as T
-import qualified Data.Text.IO as T
-import Numeric (showHex)
-import Test.QuickCheck (Arbitrary, arbitrary)
+module VeriFuzz.CodeGen
+ ( -- * Code Generation
+ GenVerilog(..)
+ , genSource
+ , render
+ ) where
+
+import Control.Lens (view, (^.))
+import Data.Foldable (fold)
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.Text.IO as T
+import Numeric (showHex)
+import Test.QuickCheck (Arbitrary, arbitrary)
import VeriFuzz.AST
+import VeriFuzz.Internal
-- | 'Source' class which determines that source code is able to be generated
-- from the data structure using 'genSource'. This will be stored in 'Text' and
@@ -30,14 +36,6 @@ import VeriFuzz.AST
class Source a where
genSource :: a -> Text
--- | Inserts commas between '[Text]' and except the last one.
-comma :: [Text] -> Text
-comma = T.intercalate ", "
-
--- | Show function for 'Text'
-showT :: (Show a) => a -> Text
-showT = T.pack . show
-
-- | Map a 'Maybe Stmnt' to 'Text'. If it is 'Just stmnt', the generated
-- statements are returned. If it is 'Nothing', then @;\n@ is returned.
defMap :: Maybe Stmnt -> Text
diff --git a/src/VeriFuzz/Internal.hs b/src/VeriFuzz/Internal.hs
index 6a880ee..3c339b5 100644
--- a/src/VeriFuzz/Internal.hs
+++ b/src/VeriFuzz/Internal.hs
@@ -13,12 +13,16 @@ Shared high level code used in the other modules internally.
module VeriFuzz.Internal
( -- * Useful functions
safe
+ , showT
+ , comma
-- * Module Specific Internals
, module VeriFuzz.Internal.Circuit
, module VeriFuzz.Internal.Simulator
, module VeriFuzz.Internal.AST
) where
+import Data.Text (Text)
+import qualified Data.Text as T
import VeriFuzz.Internal.AST
import VeriFuzz.Internal.Circuit
import VeriFuzz.Internal.Simulator
@@ -27,3 +31,11 @@ import VeriFuzz.Internal.Simulator
safe :: ([a] -> b) -> [a] -> Maybe b
safe _ [] = Nothing
safe f l = Just $ f l
+
+-- | Show function for 'Text'
+showT :: (Show a) => a -> Text
+showT = T.pack . show
+
+-- | Inserts commas between '[Text]' and except the last one.
+comma :: [Text] -> Text
+comma = T.intercalate ", "
diff --git a/src/VeriFuzz/Mutate.hs b/src/VeriFuzz/Mutate.hs
index d012358..56db6c4 100644
--- a/src/VeriFuzz/Mutate.hs
+++ b/src/VeriFuzz/Mutate.hs
@@ -18,7 +18,6 @@ import Data.Maybe (catMaybes, fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import VeriFuzz.AST
-import VeriFuzz.CodeGen
import VeriFuzz.Internal
-- | Return if the 'Identifier' is in a 'ModDecl'.
@@ -74,8 +73,12 @@ nestUpTo :: Int -> VerilogSrc -> VerilogSrc
nestUpTo i src = foldl (flip nestSource) src $ Identifier . fromNode <$> [1 .. i]
allVars :: ModDecl -> [Identifier]
-allVars m = (m ^.. modOutPorts . traverse . portName) ++ (m ^.. modInPorts . traverse . portName)
+allVars m =
+ (m ^.. modOutPorts . traverse . portName)
+ <> (m ^.. modInPorts . traverse . portName)
+
-- $setup
+-- >>> import VeriFuzz.CodeGen
-- >>> let m = (ModDecl (Identifier "m") [Port Wire 5 (Identifier "y")] [Port Wire 5 "x"] [])
-- >>> let main = (ModDecl "main" [] [] [])