简体   繁体   English

用于生成无偏图进行快速检查的任意实例

[英]Arbitrary instance for generating unbiased graphs for quickcheck

module Main where

import Test.QuickCheck
import Data.Set as Set    

data Edge v = Edge {source :: v, target :: v}
                  deriving (Show,Eq,Ord)

data Graph v = Graph {nodes :: Set v, edges :: Set (Edge v)}
               deriving Show

instance Arbitrary v => Int-> Arbitrary (Edge v) where
    arbitrary = sized aux 
        where aux n = do s <- arbitrary
                         t <- arbitrary `suchThat` (/= s)
                         return $ Edge {source = s, target = t}


instance (Ord v, Arbitrary v) => Arbitrary (Graph v) where
    arbitrary = aux `suchThat` isValid
        where aux = do ns <- arbitrary 
                       es <- arbitrary 
                       return $ Graph {nodes = fromList ns, edges = fromList es}

This current definition of the instance is generating graphs with few edges, how do I alter it so it's less biased and it satisfies these two functions? 实例的当前定义正在生成几乎没有边缘的图,如何更改它以减少偏见并满足这两个功能? :

-- | -| The function 'isDAG' tests if the graph is acyclic. 函数“ isDAG”测试图是否为非循环图。

isDAG :: Ord v => Graph v -> Bool
isDAG g = isValid g && all nocycle (nodes g)
    where nocycle v = all (\a -> v `notMember` reachable g a) $ Set.map target (adj g v)

-- | -| The function 'isForest' tests if a valid DAG is a florest (a set of trees), in other words, -- if every node(vertex) has a maximum of one adjacent. 函数'isForest'测试一个有效的DAG是否是一个小植物(一组树),换句话说,-如果每个节点(顶点)最多具有一个相邻节点。

isForest :: Ord v => DAG v -> Bool
isForest g = isDAG g && all (\v -> length (adj g v) <= 1) (nodes g)

First you must figure out how to construct a graph which satisfies those properties. 首先,您必须弄清楚如何构造满足这些属性的图。

DAG: If your nodes admit some ordering, and for each edge (u,v) you have u < v then the graph is acyclic. DAG:如果您的节点接受某种排序,并且对于每个边(u,v)您的u < v则该图是非循环的。 This ordering can be any ordering at all, so you can just manufacture an arbitrary ordering on the set of nodes in the graph. 此排序完全可以是任何排序,因此您可以在图形中的节点集上制造任意排序。

Forest: If your graph has no edges, this property is trivially satisfied. 森林:如果图形没有边,则可以轻松满足此属性。 Initially you can add any edge whose source is any node. 最初,您可以添加源为任何节点的任何边。 If you add an edge, remove the source of that edge from the remaining available nodes. 如果添加边缘,请从其余可用节点中删除该边缘的源。

I guess the big question is how to translate this to code. 我想最大的问题是如何将其转换为代码。 QuickCheck provides many combinators, esp. QuickCheck提供了许多组合器,尤其是。 for selecting from lists, with and without replacement, of various sizes, etc. 用于从列表中进行选择,有或没有替代品,各种尺寸等。

instance (Ord v, Arbitrary v) => Arbitrary (Graph v) where 
  arbitrary = do 
    ns <- Set.fromList <$> liftA2 (++) (replicateM 10 arbitrary) arbitrary

First you generate a random set of nodes. 首先,您生成一组随机节点。

    let ns' = map reverse $ drop 2 $ inits $ Set.toList ns 

For each node, this computes the (non-empty) set of nodes which are "greater" than that node. 对于每个节点,这将计算(大于)该节点“(非空)”的节点集。 Here "greater" just means according to the arbitrary ordering induced by the order of the elements in the list. 在这里,“更大”仅表示根据列表中元素顺序产生的任意顺序。 This gets you the DAG property. 这将为您提供DAG属性。

    es <- sublistOf ns' >>= 
            mapM (\(f:ts) -> Edge f <$> elements ts)

You then get a random sublist of that list (which gets you the forest property), and for each element in that random sublist, you create an edge pointing from the "largest" node in that set to one that is "smaller". 然后,您将获得该列表的一个随机子列表(这将为您提供林属性),并为该随机子列表中的每个元素创建一条从该集合中“最大”节点指向“较小”节点的边。

    return $ Graph ns (Set.fromList es) 

Then you're done! 这样就完成了! Test like so: 像这样测试:

main = quickCheck $ forAll arbitrary (liftA2 (&&) (isDAG :: Graph Integer -> Bool) isForest)

A natural way of constructing graphs is inductively, adding one node at a time. 构造图的一种自然方法是归纳法,一次添加一个节点。 Then it becomes quite easy to ensure the required properties hold: 然后,确保所需的属性成立变得非常容易:

  • If for each added node its edges point only to existing nodes (and not in the other direction), we ensure the DAG property. 如果对于每个添加的节点,其边缘仅指向现有节点(而不指向另一个方向),则确保DAG属性。
  • If there is at most one edge going from a node, we ensure the forest property. 如果一个节点最多有一条边缘,则确保林属性。 (As you didn't provide the adj function, it's not clear if by "forest" you mean there is at most one edge going from a node or to a node.) (由于您未提供adj函数,因此不清楚“森林”是否意味着一个节点一个节点最多有一条边。)

So the process of generating such a graph would go as follows: 因此,生成此类图的过程将如下所示:

  1. Generate a list of random nodes. 生成随机节点列表。
  2. Construct a graph by add them one by one. 通过一张一张地添加它们来构造图。 For each node, either add a random edge to one of the already added nodes, or no edge (decide randomly). 对于每个节点,可以将随机边缘添加到已添加的节点之一,或者不添加边缘(随机确定)。

The main factor here is deciding whether to add an edge or not. 此处的主要因素是确定是否添加边。 By tweaking this parameter you get more or less trees in your forest. 通过调整此参数,您可以在森林中获得更多或更少的树木。 One option is to use frequency for that. 一种选择是为此使用frequency

声明:本站的技术帖子网页,遵循CC BY-SA 4.0协议,如果您需要转载,请注明本站网址或者原文地址。任何问题请咨询:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM