aboutsummaryrefslogtreecommitdiffstats
path: root/src/Verismith/Circuit
diff options
context:
space:
mode:
Diffstat (limited to 'src/Verismith/Circuit')
-rw-r--r--src/Verismith/Circuit/Base.hs51
-rw-r--r--src/Verismith/Circuit/Gen.hs60
-rw-r--r--src/Verismith/Circuit/Internal.hs52
-rw-r--r--src/Verismith/Circuit/Random.hs78
4 files changed, 120 insertions, 121 deletions
diff --git a/src/Verismith/Circuit/Base.hs b/src/Verismith/Circuit/Base.hs
index 9a5ab34..804fbfd 100644
--- a/src/Verismith/Circuit/Base.hs
+++ b/src/Verismith/Circuit/Base.hs
@@ -1,40 +1,39 @@
-{-|
-Module : Verismith.Circuit.Base
-Description : Base types for the circuit module.
-Copyright : (c) 2019, Yann Herklotz Grave
-License : GPL-3
-Maintainer : yann [at] yannherklotz [dot] com
-Stability : experimental
-Portability : POSIX
-
-Base types for the circuit module.
--}
-
+-- |
+-- Module : Verismith.Circuit.Base
+-- Description : Base types for the circuit module.
+-- Copyright : (c) 2019, Yann Herklotz Grave
+-- License : GPL-3
+-- Maintainer : yann [at] yannherklotz [dot] com
+-- Stability : experimental
+-- Portability : POSIX
+--
+-- Base types for the circuit module.
module Verismith.Circuit.Base
- ( Gate(..)
- , Circuit(..)
- , CNode(..)
- , CEdge(..)
- )
+ ( Gate (..),
+ Circuit (..),
+ CNode (..),
+ CEdge (..),
+ )
where
-import Data.Graph.Inductive (Gr, LEdge, LNode)
-import System.Random
+import Data.Graph.Inductive (Gr, LEdge, LNode)
+import System.Random
-- | The types for all the gates.
-data Gate = And
- | Or
- | Xor
- deriving (Show, Eq, Enum, Bounded, Ord)
+data Gate
+ = And
+ | Or
+ | Xor
+ deriving (Show, Eq, Enum, Bounded, Ord)
-- | Newtype for the Circuit which implements a Graph from fgl.
-newtype Circuit = Circuit { getCircuit :: Gr Gate () }
+newtype Circuit = Circuit {getCircuit :: Gr Gate ()}
-- | Newtype for a node in the circuit, which is an 'LNode Gate'.
-newtype CNode = CNode { getCNode :: LNode Gate }
+newtype CNode = CNode {getCNode :: LNode Gate}
-- | Newtype for a named edge which is empty, as it does not need a label.
-newtype CEdge = CEdge { getCEdge :: LEdge () }
+newtype CEdge = CEdge {getCEdge :: LEdge ()}
instance Random Gate where
randomR (a, b) g =
diff --git a/src/Verismith/Circuit/Gen.hs b/src/Verismith/Circuit/Gen.hs
index 07b6c06..7b3f072 100644
--- a/src/Verismith/Circuit/Gen.hs
+++ b/src/Verismith/Circuit/Gen.hs
@@ -1,27 +1,25 @@
-{-|
-Module : Verilog.Circuit.Gen
-Description : Generate verilog from circuit.
-Copyright : (c) 2019, Yann Herklotz Grave
-License : GPL-3
-Maintainer : yann [at] yannherklotz [dot] com
-Stability : experimental
-Portability : POSIX
-
-Generate verilog from circuit.
--}
-
+-- |
+-- Module : Verilog.Circuit.Gen
+-- Description : Generate verilog from circuit.
+-- Copyright : (c) 2019, Yann Herklotz Grave
+-- License : GPL-3
+-- Maintainer : yann [at] yannherklotz [dot] com
+-- Stability : experimental
+-- Portability : POSIX
+--
+-- Generate verilog from circuit.
module Verismith.Circuit.Gen
- ( generateAST
- )
+ ( generateAST,
+ )
where
-import Data.Graph.Inductive (LNode, Node)
-import qualified Data.Graph.Inductive as G
-import Data.Maybe (catMaybes)
-import Verismith.Circuit.Base
-import Verismith.Circuit.Internal
-import Verismith.Verilog.AST
-import Verismith.Verilog.Mutate
+import Data.Graph.Inductive (LNode, Node)
+import qualified Data.Graph.Inductive as G
+import Data.Maybe (catMaybes)
+import Verismith.Circuit.Base
+import Verismith.Circuit.Internal
+import Verismith.Verilog.AST
+import Verismith.Verilog.Mutate
-- | Converts a 'CNode' to an 'Identifier'.
frNode :: Node -> Identifier
@@ -31,7 +29,7 @@ frNode = Identifier . fromNode
-- mapping.
fromGate :: Gate -> BinaryOperator
fromGate And = BinAnd
-fromGate Or = BinOr
+fromGate Or = BinOr
fromGate Xor = BinXor
inputsC :: Circuit -> [Node]
@@ -43,8 +41,8 @@ genPortsAST f c = port . frNode <$> f c where port = Port Wire False 4
-- | Generates the nested expression AST, so that it can then generate the
-- assignment expressions.
genAssignExpr :: Gate -> [Node] -> Maybe Expr
-genAssignExpr _ [] = Nothing
-genAssignExpr _ [n ] = Just . Id $ frNode n
+genAssignExpr _ [] = Nothing
+genAssignExpr _ [n] = Just . Id $ frNode n
genAssignExpr g (n : ns) = BinOp wire oper <$> genAssignExpr g ns
where
wire = Id $ frNode n
@@ -56,24 +54,24 @@ genAssignExpr g (n : ns) = BinOp wire oper <$> genAssignExpr g ns
genContAssignAST :: Circuit -> LNode Gate -> Maybe (ModItem ann)
genContAssignAST c (n, g) = ModCA . ContAssign name <$> genAssignExpr g nodes
where
- gr = getCircuit c
+ gr = getCircuit c
nodes = G.pre gr n
- name = frNode n
+ name = frNode n
genAssignAST :: Circuit -> [ModItem ann]
genAssignAST c = catMaybes $ genContAssignAST c <$> nodes
where
- gr = getCircuit c
+ gr = getCircuit c
nodes = G.labNodes gr
genModuleDeclAST :: Circuit -> (ModDecl ann)
genModuleDeclAST c = ModDecl i output ports (combineAssigns yPort a) []
where
- i = Identifier "gen_module"
- ports = genPortsAST inputsC c
+ i = Identifier "gen_module"
+ ports = genPortsAST inputsC c
output = []
- a = genAssignAST c
- yPort = Port Wire False 90 "y"
+ a = genAssignAST c
+ yPort = Port Wire False 90 "y"
generateAST :: Circuit -> (Verilog ann)
generateAST c = Verilog [genModuleDeclAST c]
diff --git a/src/Verismith/Circuit/Internal.hs b/src/Verismith/Circuit/Internal.hs
index f727630..ead1de8 100644
--- a/src/Verismith/Circuit/Internal.hs
+++ b/src/Verismith/Circuit/Internal.hs
@@ -1,27 +1,25 @@
-{-|
-Module : Verismith.Circuit.Internal
-Description : Internal helpers for generation.
-Copyright : (c) 2018-2019, Yann Herklotz
-License : GPL-3
-Maintainer : yann [at] yannherklotz [dot] com
-Stability : experimental
-Portability : POSIX
-
-Internal helpers for generation.
--}
-
+-- |
+-- Module : Verismith.Circuit.Internal
+-- Description : Internal helpers for generation.
+-- Copyright : (c) 2018-2019, Yann Herklotz
+-- License : GPL-3
+-- Maintainer : yann [at] yannherklotz [dot] com
+-- Stability : experimental
+-- Portability : POSIX
+--
+-- Internal helpers for generation.
module Verismith.Circuit.Internal
- ( fromNode
- , filterGr
- , only
- , inputs
- , outputs
- )
+ ( fromNode,
+ filterGr,
+ only,
+ inputs,
+ outputs,
+ )
where
-import Data.Graph.Inductive (Graph, Node)
+import Data.Graph.Inductive (Graph, Node)
import qualified Data.Graph.Inductive as G
-import qualified Data.Text as T
+import qualified Data.Text as T
-- | Convert an integer into a label.
--
@@ -36,13 +34,13 @@ filterGr graph f = filter f $ G.nodes graph
-- | Takes two functions that return an 'Int', and compares there results to 0
-- and not 0 respectively. This result is returned.
-only
- :: (Graph gr)
- => gr n e
- -> (gr n e -> Node -> Int)
- -> (gr n e -> Node -> Int)
- -> Node
- -> Bool
+only ::
+ (Graph gr) =>
+ gr n e ->
+ (gr n e -> Node -> Int) ->
+ (gr n e -> Node -> Int) ->
+ Node ->
+ Bool
only graph fun1 fun2 n = fun1 graph n == 0 && fun2 graph n /= 0
-- | Returns all the input nodes to a graph, which means nodes that do not have
diff --git a/src/Verismith/Circuit/Random.hs b/src/Verismith/Circuit/Random.hs
index 5389df8..4d00c24 100644
--- a/src/Verismith/Circuit/Random.hs
+++ b/src/Verismith/Circuit/Random.hs
@@ -1,35 +1,34 @@
-{-|
-Module : Verismith.Circuit.Random
-Description : Random generation for DAG
-Copyright : (c) 2018-2019, Yann Herklotz
-License : GPL-3
-Maintainer : yann [at] yannherklotz [dot] com
-Stability : experimental
-Portability : POSIX
-
-Define the random generation for the directed acyclic graph.
--}
-
+-- |
+-- Module : Verismith.Circuit.Random
+-- Description : Random generation for DAG
+-- Copyright : (c) 2018-2019, Yann Herklotz
+-- License : GPL-3
+-- Maintainer : yann [at] yannherklotz [dot] com
+-- Stability : experimental
+-- Portability : POSIX
+--
+-- Define the random generation for the directed acyclic graph.
module Verismith.Circuit.Random
- ( rDups
- , rDupsCirc
- , randomDAG
- , genRandomDAG
- )
+ ( rDups,
+ rDupsCirc,
+ randomDAG,
+ genRandomDAG,
+ )
where
-import Data.Graph.Inductive (Context)
-import qualified Data.Graph.Inductive as G
-import Data.Graph.Inductive.PatriciaTree (Gr)
-import Data.List (nub)
-import Hedgehog (Gen)
-import qualified Hedgehog.Gen as Hog
-import qualified Hedgehog.Range as Hog
-import Verismith.Circuit.Base
+import Data.Graph.Inductive (Context)
+import qualified Data.Graph.Inductive as G
+import Data.Graph.Inductive.PatriciaTree (Gr)
+import Data.List (nub)
+import Hedgehog (Gen)
+import qualified Hedgehog.Gen as Hog
+import qualified Hedgehog.Range as Hog
+import Verismith.Circuit.Base
dupFolder :: (Eq a, Eq b) => Context a b -> [Context a b] -> [Context a b]
dupFolder cont ns = unique cont : ns
- where unique (a, b, c, d) = (nub a, b, c, nub d)
+ where
+ unique (a, b, c, d) = (nub a, b, c, nub d)
-- | Remove duplicates.
rDups :: (Eq a, Eq b) => Gr a b -> Gr a b
@@ -43,21 +42,26 @@ rDupsCirc = Circuit . rDups . getCircuit
-- `n` that is passed to it.
arbitraryEdge :: Hog.Size -> Gen CEdge
arbitraryEdge n = do
- x <- with $ \a -> a < n && a > 0 && a /= n - 1
- y <- with $ \a -> x < a && a < n && a > 0
- return $ CEdge (fromIntegral x, fromIntegral y, ())
+ x <- with $ \a -> a < n && a > 0 && a /= n - 1
+ y <- with $ \a -> x < a && a < n && a > 0
+ return $ CEdge (fromIntegral x, fromIntegral y, ())
where
- with = flip Hog.filter $ fromIntegral <$> Hog.resize
- n
- (Hog.int (Hog.linear 0 100))
+ with =
+ flip Hog.filter $
+ fromIntegral
+ <$> Hog.resize
+ n
+ (Hog.int (Hog.linear 0 100))
-- | Gen instance for a random acyclic DAG.
-randomDAG :: Gen Circuit -- ^ The generated graph. It uses Arbitrary to generate
- -- random instances of each node
+randomDAG ::
+ -- | The generated graph. It uses Arbitrary to generate
+ -- random instances of each node
+ Gen Circuit
randomDAG = do
- list <- Hog.list (Hog.linear 1 100) $ Hog.enum minBound maxBound
- l <- Hog.list (Hog.linear 10 1000) aE
- return . Circuit $ G.mkGraph (nodes list) l
+ list <- Hog.list (Hog.linear 1 100) $ Hog.enum minBound maxBound
+ l <- Hog.list (Hog.linear 10 1000) aE
+ return . Circuit $ G.mkGraph (nodes list) l
where
nodes l = zip [0 .. length l - 1] l
aE = getCEdge <$> Hog.sized arbitraryEdge