fgl-arbitrary-0.2.0.5: QuickCheck support for fgl

Copyright(c) Ivan Lazar Miljenovic
LicenseBSD3
MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone
LanguageHaskell2010

Data.Graph.Inductive.Arbitrary

Contents

Description

This module provides default definitions for use with QuickCheck's Arbitrary class.

Both Data.Graph.Inductive.Tree- and Data.Graph.Inductive.PatriciaTree-based graph implementations have Arbitrary instances. In most cases, this is all you will need.

If, however, you want to create arbitrary custom graph-like data structures, then you will probably want to do some custom processing from an arbitrary GraphNodesEdges value, either directly or with a custom ArbGraph instance.

Synopsis

Explicit graph creation

If you wish to explicitly create a generated graph value (rather than using the Arbitrary class) then you will want to use these functions.

arbitraryGraph :: (Graph gr, Arbitrary a, Arbitrary b) => Gen (gr a b) Source #

Generate an arbitrary graph. Multiple edges are allowed.

arbitraryGraphWith :: (Graph gr, Arbitrary a, Arbitrary b) => ([LEdge b] -> [LEdge b]) -> Gen (gr a b) Source #

Generate an arbitrary graph, using the specified function to manipulate the generated list of edges (e.g. remove multiple edges).

shrinkGraph :: Graph gr => gr a b -> [gr a b] Source #

For a graph with at least two nodes, return every possible way of deleting a single node (i.e. will never shrink to an empty graph).

shrinkGraphWith :: Graph gr => gr a b -> [(Node, gr a b)] Source #

As with shrinkGraph, but also return the node that was deleted.

Types of graphs

class DynGraph (BaseGraph ag) => ArbGraph ag where Source #

Representation of generating arbitrary graph structures.

Typically, you would only use this for the toBaseGraph function or if you wanted to make a custom graph wrapper.

The intent of this class is to simplify defining and using different wrappers on top of graphs (e.g. you may wish to have an Undirected graph, or one with NoLoops, or possibly both!).

Associated Types

type BaseGraph ag :: * -> * -> * Source #

Methods

toBaseGraph :: ag a b -> BaseGraph ag a b Source #

fromBaseGraph :: BaseGraph ag a b -> ag a b Source #

edgeF :: GrProxy ag -> [LEdge b] -> [LEdge b] Source #

Any manipulation of edges that should be done to satisfy the requirements of the specified wrapper.

shrinkFWith :: ag a b -> [(Node, ag a b)] Source #

Shrinking function (assuming only one node is removed at a time) which also returns the node that is removed.

Instances
ArbGraph Gr Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Associated Types

type BaseGraph Gr :: Type -> Type -> Type Source #

Methods

toBaseGraph :: Gr a b -> BaseGraph Gr a b Source #

fromBaseGraph :: BaseGraph Gr a b -> Gr a b Source #

edgeF :: GrProxy Gr -> [LEdge b] -> [LEdge b] Source #

shrinkFWith :: Gr a b -> [(Node, Gr a b)] Source #

ArbGraph Gr Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Associated Types

type BaseGraph Gr :: Type -> Type -> Type Source #

Methods

toBaseGraph :: Gr a b -> BaseGraph Gr a b Source #

fromBaseGraph :: BaseGraph Gr a b -> Gr a b Source #

edgeF :: GrProxy Gr -> [LEdge b] -> [LEdge b] Source #

shrinkFWith :: Gr a b -> [(Node, Gr a b)] Source #

ArbGraph gr => ArbGraph (Undirected gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Associated Types

type BaseGraph (Undirected gr) :: Type -> Type -> Type Source #

Methods

toBaseGraph :: Undirected gr a b -> BaseGraph (Undirected gr) a b Source #

fromBaseGraph :: BaseGraph (Undirected gr) a b -> Undirected gr a b Source #

edgeF :: GrProxy (Undirected gr) -> [LEdge b] -> [LEdge b] Source #

shrinkFWith :: Undirected gr a b -> [(Node, Undirected gr a b)] Source #

ArbGraph gr => ArbGraph (NoLoops gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Associated Types

type BaseGraph (NoLoops gr) :: Type -> Type -> Type Source #

Methods

toBaseGraph :: NoLoops gr a b -> BaseGraph (NoLoops gr) a b Source #

fromBaseGraph :: BaseGraph (NoLoops gr) a b -> NoLoops gr a b Source #

edgeF :: GrProxy (NoLoops gr) -> [LEdge b] -> [LEdge b] Source #

shrinkFWith :: NoLoops gr a b -> [(Node, NoLoops gr a b)] Source #

ArbGraph gr => ArbGraph (NoMultipleEdges gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Associated Types

type BaseGraph (NoMultipleEdges gr) :: Type -> Type -> Type Source #

data GrProxy (gr :: * -> * -> *) Source #

A simple graph-specific proxy type.

Constructors

GrProxy 
Instances
Eq (GrProxy gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

(==) :: GrProxy gr -> GrProxy gr -> Bool #

(/=) :: GrProxy gr -> GrProxy gr -> Bool #

Ord (GrProxy gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

compare :: GrProxy gr -> GrProxy gr -> Ordering #

(<) :: GrProxy gr -> GrProxy gr -> Bool #

(<=) :: GrProxy gr -> GrProxy gr -> Bool #

(>) :: GrProxy gr -> GrProxy gr -> Bool #

(>=) :: GrProxy gr -> GrProxy gr -> Bool #

max :: GrProxy gr -> GrProxy gr -> GrProxy gr #

min :: GrProxy gr -> GrProxy gr -> GrProxy gr #

Read (GrProxy gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Show (GrProxy gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

showsPrec :: Int -> GrProxy gr -> ShowS #

show :: GrProxy gr -> String #

showList :: [GrProxy gr] -> ShowS #

shrinkF :: ArbGraph ag => ag a b -> [ag a b] Source #

In most cases, for an instance of ArbGraph the Arbitrary instance definition will/can have shrink = shrinkF.

arbitraryGraphBy :: forall ag a b. (ArbGraph ag, Arbitrary a, Arbitrary b) => Gen (ag a b) Source #

Generate an instance of ArbGraph using the class methods.

Specific graph structures

newtype NoMultipleEdges gr a b Source #

A newtype wrapper to generate a graph without multiple edges (loops allowed).

Constructors

NME 

Fields

Instances
ArbGraph gr => ArbGraph (NoMultipleEdges gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Associated Types

type BaseGraph (NoMultipleEdges gr) :: Type -> Type -> Type Source #

Eq (gr a b) => Eq (NoMultipleEdges gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

(==) :: NoMultipleEdges gr a b -> NoMultipleEdges gr a b -> Bool #

(/=) :: NoMultipleEdges gr a b -> NoMultipleEdges gr a b -> Bool #

Read (gr a b) => Read (NoMultipleEdges gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Show (gr a b) => Show (NoMultipleEdges gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

showsPrec :: Int -> NoMultipleEdges gr a b -> ShowS #

show :: NoMultipleEdges gr a b -> String #

showList :: [NoMultipleEdges gr a b] -> ShowS #

(ArbGraph gr, Arbitrary a, Arbitrary b) => Arbitrary (NoMultipleEdges gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

arbitrary :: Gen (NoMultipleEdges gr a b) #

shrink :: NoMultipleEdges gr a b -> [NoMultipleEdges gr a b] #

type BaseGraph (NoMultipleEdges gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

newtype NoLoops gr a b Source #

A newtype wrapper to generate a graph without loops (multiple edges allowed).

Constructors

NL 

Fields

Instances
ArbGraph gr => ArbGraph (NoLoops gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Associated Types

type BaseGraph (NoLoops gr) :: Type -> Type -> Type Source #

Methods

toBaseGraph :: NoLoops gr a b -> BaseGraph (NoLoops gr) a b Source #

fromBaseGraph :: BaseGraph (NoLoops gr) a b -> NoLoops gr a b Source #

edgeF :: GrProxy (NoLoops gr) -> [LEdge b] -> [LEdge b] Source #

shrinkFWith :: NoLoops gr a b -> [(Node, NoLoops gr a b)] Source #

Eq (gr a b) => Eq (NoLoops gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

(==) :: NoLoops gr a b -> NoLoops gr a b -> Bool #

(/=) :: NoLoops gr a b -> NoLoops gr a b -> Bool #

Read (gr a b) => Read (NoLoops gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

readsPrec :: Int -> ReadS (NoLoops gr a b) #

readList :: ReadS [NoLoops gr a b] #

readPrec :: ReadPrec (NoLoops gr a b) #

readListPrec :: ReadPrec [NoLoops gr a b] #

Show (gr a b) => Show (NoLoops gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

showsPrec :: Int -> NoLoops gr a b -> ShowS #

show :: NoLoops gr a b -> String #

showList :: [NoLoops gr a b] -> ShowS #

(ArbGraph gr, Arbitrary a, Arbitrary b) => Arbitrary (NoLoops gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

arbitrary :: Gen (NoLoops gr a b) #

shrink :: NoLoops gr a b -> [NoLoops gr a b] #

type BaseGraph (NoLoops gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

type BaseGraph (NoLoops gr) = BaseGraph gr

type SimpleGraph gr = NoLoops (NoMultipleEdges gr) Source #

A wrapper to generate a graph without multiple edges and no loops.

newtype Undirected gr a b Source #

A newtype wrapper such that each (non-loop) edge also has its reverse in the graph.

Note that there is no way to guarantee this after any additional edges are added or removed.

You should also apply this wrapper after NoMultipleEdges or else the wrong reverse edge might be removed.

Constructors

UG 

Fields

Instances
ArbGraph gr => ArbGraph (Undirected gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Associated Types

type BaseGraph (Undirected gr) :: Type -> Type -> Type Source #

Methods

toBaseGraph :: Undirected gr a b -> BaseGraph (Undirected gr) a b Source #

fromBaseGraph :: BaseGraph (Undirected gr) a b -> Undirected gr a b Source #

edgeF :: GrProxy (Undirected gr) -> [LEdge b] -> [LEdge b] Source #

shrinkFWith :: Undirected gr a b -> [(Node, Undirected gr a b)] Source #

Eq (gr a b) => Eq (Undirected gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

(==) :: Undirected gr a b -> Undirected gr a b -> Bool #

(/=) :: Undirected gr a b -> Undirected gr a b -> Bool #

Read (gr a b) => Read (Undirected gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Show (gr a b) => Show (Undirected gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

showsPrec :: Int -> Undirected gr a b -> ShowS #

show :: Undirected gr a b -> String #

showList :: [Undirected gr a b] -> ShowS #

(ArbGraph gr, Arbitrary a, Arbitrary b) => Arbitrary (Undirected gr a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

arbitrary :: Gen (Undirected gr a b) #

shrink :: Undirected gr a b -> [Undirected gr a b] #

type BaseGraph (Undirected gr) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Connected graphs

data Connected ag a b Source #

A brute-force approach to generating connected graphs.

The resultant graph (obtained with connGraph) will never be empty: it will, at the very least, contain an additional connected node (obtained with connNode).

Note that this is not an instance of ArbGraph as it is not possible to arbitrarily layer a transformer on top of this.

Constructors

CG 

Fields

Instances
Eq (ag a b) => Eq (Connected ag a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

(==) :: Connected ag a b -> Connected ag a b -> Bool #

(/=) :: Connected ag a b -> Connected ag a b -> Bool #

Read (ag a b) => Read (Connected ag a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

readsPrec :: Int -> ReadS (Connected ag a b) #

readList :: ReadS [Connected ag a b] #

readPrec :: ReadPrec (Connected ag a b) #

readListPrec :: ReadPrec [Connected ag a b] #

Show (ag a b) => Show (Connected ag a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

showsPrec :: Int -> Connected ag a b -> ShowS #

show :: Connected ag a b -> String #

showList :: [Connected ag a b] -> ShowS #

(ArbGraph ag, Arbitrary a, Arbitrary b) => Arbitrary (Connected ag a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Methods

arbitrary :: Gen (Connected ag a b) #

shrink :: Connected ag a b -> [Connected ag a b] #

connGraph :: ArbGraph ag => Connected ag a b -> BaseGraph ag a b Source #

The underlying graph represented by this Connected value.

Node and edge lists

arbitraryNodes :: Arbitrary a => Gen [LNode a] Source #

Generally a list of labelled nodes.

arbitraryEdges :: Arbitrary b => [LNode a] -> Gen [LEdge b] Source #

Given a specified list of nodes, generate a list of edges.

data GraphNodesEdges a b Source #

Defined so as to be able to generate valid arbitrary node and edge lists.

If any specific structure (no multiple edges, no loops, etc.) is required then you will need to post-process this after generating it, or else create a new instance of ArbGraph.

Constructors

GNEs 

Fields

Instances
(Eq a, Eq b) => Eq (GraphNodesEdges a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

(Ord a, Ord b) => Ord (GraphNodesEdges a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

(Read a, Read b) => Read (GraphNodesEdges a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

(Show a, Show b) => Show (GraphNodesEdges a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

(Arbitrary a, Arbitrary b) => Arbitrary (GraphNodesEdges a b) Source # 
Instance details

Defined in Data.Graph.Inductive.Arbitrary

Orphan instances

(Arbitrary a, Arbitrary b) => Arbitrary (Gr a b) Source # 
Instance details

Methods

arbitrary :: Gen (Gr a b) #

shrink :: Gr a b -> [Gr a b] #

(Arbitrary a, Arbitrary b) => Arbitrary (Gr a b) Source # 
Instance details

Methods

arbitrary :: Gen (Gr a b) #

shrink :: Gr a b -> [Gr a b] #