aboutsummaryrefslogtreecommitdiffstats
path: root/src
diff options
context:
space:
mode:
authorYann Herklotz <git@ymhg.org>2019-04-02 13:00:26 +0100
committerYann Herklotz <git@ymhg.org>2019-04-02 13:00:26 +0100
commitc2accfb8cc182e591021efef7a2ad9b6ebc13a1e (patch)
treee6e60955235cb354132748367906d0b8abcaa003 /src
parent5c9683df241fe6dada5cb8338d38d7068e8ac0ce (diff)
downloadverismith-c2accfb8cc182e591021efef7a2ad9b6ebc13a1e.tar.gz
verismith-c2accfb8cc182e591021efef7a2ad9b6ebc13a1e.zip
Fix random generation for Circuit
Diffstat (limited to 'src')
-rw-r--r--src/VeriFuzz/Random.hs48
1 files changed, 29 insertions, 19 deletions
diff --git a/src/VeriFuzz/Random.hs b/src/VeriFuzz/Random.hs
index ef9e14c..4330543 100644
--- a/src/VeriFuzz/Random.hs
+++ b/src/VeriFuzz/Random.hs
@@ -12,12 +12,13 @@ Define the random generation for the directed acyclic graph.
module VeriFuzz.Random where
-import Data.Graph.Inductive (Context, LEdge)
+import Data.Graph.Inductive (Context)
import qualified Data.Graph.Inductive as G
import Data.Graph.Inductive.PatriciaTree (Gr)
import Data.List (nub)
-import Test.QuickCheck (Arbitrary, Gen)
-import qualified Test.QuickCheck as QC
+import Hedgehog (Gen)
+import qualified Hedgehog.Gen as Hog
+import qualified Hedgehog.Range as Hog
import VeriFuzz.Circuit
dupFolder :: (Eq a, Eq b) => Context a b -> [Context a b] -> [Context a b]
@@ -34,29 +35,38 @@ rDupsCirc = Circuit . rDups . getCircuit
-- | Gen instance to create an arbitrary edge, where the edges are limited by
-- `n` that is passed to it.
-arbitraryEdge :: (Arbitrary e) => Int -> Gen (LEdge e)
+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
- z <- QC.arbitrary
- return (x, y, z)
- where with = QC.suchThat $ QC.resize n QC.arbitrary
+ return $ CEdge (fromIntegral x, fromIntegral y, ())
+ where
+ with = flip Hog.filter $ fromIntegral <$> Hog.resize
+ n
+ (Hog.int (Hog.linear 0 100))
-- | Gen instance for a random acyclic DAG.
-randomDAG :: (Arbitrary l, Arbitrary e, Eq l, Eq e) => Gen (Gr l e) -- ^ The generated graph. It uses Arbitrary to
- -- generate random instances of each node
+randomDAG :: Gen Circuit -- ^ The generated graph. It uses Arbitrary to generate
+ -- random instances of each node
randomDAG = do
- list <- QC.infiniteListOf QC.arbitrary
- l <- QC.infiniteListOf aE
- QC.sized (\n -> return . G.mkGraph (nodes list n) $ take (10 * n) 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 n = zip [0 .. n] $ take n l
- aE = QC.sized arbitraryEdge
+ nodes l = zip [0 .. length l - 1] l
+ aE = getCEdge <$> Hog.sized arbitraryEdge
-- | Generate a random acyclic DAG with an IO instance.
-genRandomDAG :: (Arbitrary l, Arbitrary e, Eq l, Eq e) => IO (Gr l e)
-genRandomDAG = QC.generate randomDAG
+genRandomDAG :: IO Circuit
+genRandomDAG = Hog.sample randomDAG
--- | Generate a random circuit instead of a random graph
-randomCircuit :: Gen Circuit
-randomCircuit = Circuit <$> randomDAG
+-- fromGraph :: Gen ModDecl
+-- fromGraph = do
+-- gr <- rDupsCirc <$> Hog.resize 100 randomCircuit
+-- return
+-- $ initMod
+-- . head
+-- $ nestUpTo 5 (generateAST gr)
+-- ^.. getVerilogSrc
+-- . traverse
+-- . getDescription