aboutsummaryrefslogtreecommitdiffstats
path: root/src/Test/VeriFuzz/Graph
diff options
context:
space:
mode:
Diffstat (limited to 'src/Test/VeriFuzz/Graph')
-rw-r--r--src/Test/VeriFuzz/Graph/CodeGen.hs18
-rw-r--r--src/Test/VeriFuzz/Graph/Random.hs16
2 files changed, 32 insertions, 2 deletions
diff --git a/src/Test/VeriFuzz/Graph/CodeGen.hs b/src/Test/VeriFuzz/Graph/CodeGen.hs
index 6f7aef6..43fee25 100644
--- a/src/Test/VeriFuzz/Graph/CodeGen.hs
+++ b/src/Test/VeriFuzz/Graph/CodeGen.hs
@@ -1,13 +1,27 @@
+{-|
+Module : Test.VeriFuzz.Graph.Random
+Description : Code generation directly from DAG.
+Copyright : (c) Yann Herklotz Grave 2018
+License : GPL-3
+Maintainer : ymherklotz@gmail.com
+Stability : experimental
+Portability : POSIX
+
+Define the code generation directly from the random DAG.
+-}
+
{-# LANGUAGE OverloadedStrings #-}
-module Test.VeriFuzz.Graph.CodeGen where
+module Test.VeriFuzz.Graph.CodeGen
+ ( generate
+ ) where
import Data.Graph.Inductive (Graph, LNode, Node, indeg,
labNodes, nodes, outdeg, pre)
import Data.Maybe (fromMaybe)
import Data.Text (Text, empty, pack)
+import Test.VeriFuzz.Circuit
import Test.VeriFuzz.Internal.Shared
-import Test.VeriFuzz.Types
fromNode :: Node -> Text
fromNode node = pack $ "w" <> show node
diff --git a/src/Test/VeriFuzz/Graph/Random.hs b/src/Test/VeriFuzz/Graph/Random.hs
index e87036c..a31e374 100644
--- a/src/Test/VeriFuzz/Graph/Random.hs
+++ b/src/Test/VeriFuzz/Graph/Random.hs
@@ -1,9 +1,23 @@
+{-|
+Module : Test.VeriFuzz.Graph.Random
+Description : Random generation for DAG
+Copyright : (c) Yann Herklotz Grave 2018
+License : GPL-3
+Maintainer : ymherklotz@gmail.com
+Stability : experimental
+Portability : POSIX
+
+Define the random generation for the directed acyclic graph.
+-}
+
module Test.VeriFuzz.Graph.Random where
import Data.Graph.Inductive (Graph, LEdge, mkGraph)
import Test.QuickCheck (Arbitrary, Gen, arbitrary, generate,
infiniteListOf, resize, suchThat)
+-- | 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 n = do
x <- with $ \a -> a < n && a > 0 && a /= n-1
@@ -13,6 +27,7 @@ arbitraryEdge n = do
where
with = suchThat . resize n $ arbitrary
+-- | Gen instance for a random acyclic DAG.
randomDAG :: (Arbitrary l, Arbitrary e, Graph gr)
=> Int -- ^ The number of nodes
-> Gen (gr l e) -- ^ The generated graph. It uses Arbitrary to
@@ -24,6 +39,7 @@ randomDAG n = do
where
nodes l = zip [0..n] $ take n l
+-- | Generate a random acyclic DAG with an IO instance.
genRandomDAG :: (Arbitrary l, Arbitrary e, Graph gr)
=> Int
-> IO (gr l e)