From 40b09529403cf7b7190a45596d36c2f200504988 Mon Sep 17 00:00:00 2001 From: Yann Herklotz Date: Sat, 29 Dec 2018 23:42:18 +0100 Subject: Add remove duplicates --- src/Test/VeriFuzz/Graph/ASTGen.hs | 4 ++-- src/Test/VeriFuzz/Graph/Random.hs | 20 ++++++++++++++++---- 2 files changed, 18 insertions(+), 6 deletions(-) (limited to 'src') diff --git a/src/Test/VeriFuzz/Graph/ASTGen.hs b/src/Test/VeriFuzz/Graph/ASTGen.hs index 28dc32a..00eb71d 100644 --- a/src/Test/VeriFuzz/Graph/ASTGen.hs +++ b/src/Test/VeriFuzz/Graph/ASTGen.hs @@ -73,11 +73,11 @@ genAssignAST c = catMaybes $ genContAssignAST c <$> nodes nodes = G.labNodes gr genModuleDeclAST :: Circuit -> ModDecl -genModuleDeclAST c = ModDecl id Nothing ports items +genModuleDeclAST c = ModDecl id output ports items where id = Identifier "gen_module" ports = genPortsAST inputsC c - outPut = safe head $ genPortsAST inputsC c + output = Just $ Port (PortNet Wire) "y" items = genAssignAST c generateAST :: Circuit -> VerilogSrc diff --git a/src/Test/VeriFuzz/Graph/Random.hs b/src/Test/VeriFuzz/Graph/Random.hs index 7f9e3e6..fa72f2f 100644 --- a/src/Test/VeriFuzz/Graph/Random.hs +++ b/src/Test/VeriFuzz/Graph/Random.hs @@ -12,11 +12,23 @@ Define the random generation for the directed acyclic graph. module Test.VeriFuzz.Graph.Random where -import Data.Graph.Inductive (Graph, LEdge, mkGraph) +import Data.Graph.Inductive (Context, Graph, LEdge) +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 +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) + +-- | Remove duplicates. +rDups :: (Eq a, Eq b) => Gr a b -> Gr a b +rDups g = G.buildGr $ G.ufold dupFolder [] g + -- | 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) @@ -29,18 +41,18 @@ arbitraryEdge n = do with = QC.suchThat $ QC.resize n QC.arbitrary -- | Gen instance for a random acyclic DAG. -randomDAG :: (Arbitrary l, Arbitrary e) +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 = do list <- QC.infiniteListOf QC.arbitrary l <- QC.infiniteListOf $ aE - QC.sized (\n -> return . mkGraph (nodes list n) $ take (10*n) l) + QC.sized (\n -> return . G.mkGraph (nodes list n) $ take (10*n) l) where nodes l n = zip [0..n] $ take n l aE = QC.sized arbitraryEdge -- | Generate a random acyclic DAG with an IO instance. -genRandomDAG :: (Arbitrary l, Arbitrary e) +genRandomDAG :: (Arbitrary l, Arbitrary e, Eq l, Eq e) => IO (Gr l e) genRandomDAG = QC.generate randomDAG -- cgit