Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Gr a b
- type UGr = Gr () ()
- class Graph (gr :: * -> * -> *) where
- mkUGraph :: Graph gr => [Node] -> [Edge] -> gr () ()
- order :: Graph gr => gr a b -> Int
- size :: Graph gr => gr a b -> Int
- nodes :: Graph gr => gr a b -> [Node]
- edges :: Graph gr => gr a b -> [Edge]
- context :: Graph gr => gr a b -> Node -> Context a b
- lab :: Graph gr => gr a b -> Node -> Maybe a
- neighbors :: Graph gr => gr a b -> Node -> [Node]
- lneighbors :: Graph gr => gr a b -> Node -> Adj b
- suc :: Graph gr => gr a b -> Node -> [Node]
- pre :: Graph gr => gr a b -> Node -> [Node]
- lsuc :: Graph gr => gr a b -> Node -> [(Node, b)]
- lpre :: Graph gr => gr a b -> Node -> [(Node, b)]
- out :: Graph gr => gr a b -> Node -> [LEdge b]
- inn :: Graph gr => gr a b -> Node -> [LEdge b]
- outdeg :: Graph gr => gr a b -> Node -> Int
- indeg :: Graph gr => gr a b -> Node -> Int
- deg :: Graph gr => gr a b -> Node -> Int
- hasNeighbor :: Graph gr => gr a b -> Node -> Node -> Bool
- hasNeighborAdj :: (Graph gr, Eq b) => gr a b -> Node -> (b, Node) -> Bool
- hasEdge :: Graph gr => gr a b -> Edge -> Bool
- hasLEdge :: (Graph gr, Eq b) => gr a b -> LEdge b -> Bool
- equal :: (Eq a, Eq b, Graph gr) => gr a b -> gr a b -> Bool
- gelem :: Graph gr => Node -> gr a b -> Bool
- gsel :: Graph gr => (Context a b -> Bool) -> gr a b -> [Context a b]
- gfold :: Graph gr => (Context a b -> [Node]) -> (Context a b -> c -> d) -> (Maybe d -> c -> c, c) -> [Node] -> gr a b -> c
- ufold :: Graph gr => (Context a b -> c -> c) -> c -> gr a b -> c
- hasLoop :: Graph gr => gr a b -> Bool
- isSimple :: Graph gr => gr a b -> Bool
- newNodes :: Graph gr => Int -> gr a b -> [Node]
- ap :: Graph gr => gr a b -> [Node]
- bfs :: Graph gr => Node -> gr a b -> [Node]
- bfsn :: Graph gr => [Node] -> gr a b -> [Node]
- bfsWith :: Graph gr => (Context a b -> c) -> Node -> gr a b -> [c]
- bfsnWith :: Graph gr => (Context a b -> c) -> [Node] -> gr a b -> [c]
- level :: Graph gr => Node -> gr a b -> [(Node, Int)]
- leveln :: Graph gr => [(Node, Int)] -> gr a b -> [(Node, Int)]
- bfe :: Graph gr => Node -> gr a b -> [Edge]
- bfen :: Graph gr => [Edge] -> gr a b -> [Edge]
- bft :: Graph gr => Node -> gr a b -> RTree
- lbft :: Graph gr => Node -> gr a b -> LRTree b
- esp :: Graph gr => Node -> Node -> gr a b -> Path
- lesp :: Graph gr => Node -> Node -> gr a b -> LPath b
- type CFun a b c = Context a b -> c
- dfs :: Graph gr => [Node] -> gr a b -> [Node]
- dfs' :: Graph gr => gr a b -> [Node]
- dfsWith :: Graph gr => CFun a b c -> [Node] -> gr a b -> [c]
- dfsWith' :: Graph gr => CFun a b c -> gr a b -> [c]
- dff :: Graph gr => [Node] -> gr a b -> [Tree Node]
- dff' :: Graph gr => gr a b -> [Tree Node]
- dffWith :: Graph gr => CFun a b c -> [Node] -> gr a b -> [Tree c]
- dffWith' :: Graph gr => CFun a b c -> gr a b -> [Tree c]
- xdfsWith :: Graph gr => CFun a b [Node] -> CFun a b c -> [Node] -> gr a b -> [c]
- xdfWith :: Graph gr => CFun a b [Node] -> CFun a b c -> [Node] -> gr a b -> ([Tree c], gr a b)
- xdffWith :: Graph gr => CFun a b [Node] -> CFun a b c -> [Node] -> gr a b -> [Tree c]
- udfs :: Graph gr => [Node] -> gr a b -> [Node]
- udfs' :: Graph gr => gr a b -> [Node]
- udff :: Graph gr => [Node] -> gr a b -> [Tree Node]
- udff' :: Graph gr => gr a b -> [Tree Node]
- udffWith :: Graph gr => CFun a b c -> [Node] -> gr a b -> [Tree c]
- udffWith' :: Graph gr => CFun a b c -> gr a b -> [Tree c]
- rdff :: Graph gr => [Node] -> gr a b -> [Tree Node]
- rdff' :: Graph gr => gr a b -> [Tree Node]
- rdfs' :: Graph gr => gr a b -> [Node]
- rdffWith :: Graph gr => CFun a b c -> [Node] -> gr a b -> [Tree c]
- rdffWith' :: Graph gr => CFun a b c -> gr a b -> [Tree c]
- topsort :: Graph gr => gr a b -> [Node]
- topsort' :: Graph gr => gr a b -> [a]
- scc :: Graph gr => gr a b -> [[Node]]
- reachable :: Graph gr => Node -> gr a b -> [Node]
- components :: Graph gr => gr a b -> [[Node]]
- noComponents :: Graph gr => gr a b -> Int
- isConnected :: Graph gr => gr a b -> Bool
- condensation :: Graph gr => gr a b -> gr [Node] ()
- dom :: Graph gr => gr a b -> Node -> [(Node, [Node])]
- iDom :: Graph gr => gr a b -> Node -> [(Node, Node)]
- type Voronoi a = LRTree a
- gvdIn :: (DynGraph gr, Real b) => [Node] -> gr a b -> Voronoi b
- gvdOut :: (Graph gr, Real b) => [Node] -> gr a b -> Voronoi b
- voronoiSet :: Node -> Voronoi b -> [Node]
- nearestNode :: Node -> Voronoi b -> Maybe Node
- nearestDist :: Node -> Voronoi b -> Maybe b
- nearestPath :: Node -> Voronoi b -> Maybe Path
- indep :: DynGraph gr => gr a b -> [Node]
- indepSize :: DynGraph gr => gr a b -> ([Node], Int)
- msTreeAt :: (Graph gr, Real b) => Node -> gr a b -> LRTree b
- msTree :: (Graph gr, Real b) => gr a b -> LRTree b
- msPath :: LRTree b -> Node -> Node -> Path
- getRevEdges :: Num b => [Edge] -> [LEdge b]
- augmentGraph :: (DynGraph gr, Num b) => gr a b -> gr a (b, b, b)
- updAdjList :: Num b => Adj (b, b, b) -> Node -> b -> Bool -> Adj (b, b, b)
- updateFlow :: (DynGraph gr, Num b) => Path -> b -> gr a (b, b, b) -> gr a (b, b, b)
- mfmg :: (DynGraph gr, Num b, Ord b) => gr a (b, b, b) -> Node -> Node -> gr a (b, b, b)
- mf :: (DynGraph gr, Num b, Ord b) => gr a b -> Node -> Node -> gr a (b, b, b)
- maxFlowgraph :: (DynGraph gr, Num b, Ord b) => gr a b -> Node -> Node -> gr a (b, b)
- maxFlow :: (DynGraph gr, Num b, Ord b) => gr a b -> Node -> Node -> b
- type Network = Gr () (Double, Double)
- ekSimple :: Network -> Node -> Node -> (Network, Double)
- ekFused :: Network -> Node -> Node -> (Network, Double)
- ekList :: Network -> Node -> Node -> (Network, Double)
- data Heap a b
- spTree :: (Graph gr, Real b) => Node -> gr a b -> LRTree b
- sp :: (Graph gr, Real b) => Node -> Node -> gr a b -> Maybe Path
- spLength :: (Graph gr, Real b) => Node -> Node -> gr a b -> Maybe b
- dijkstra :: (Graph gr, Real b) => Heap b (LPath b) -> gr a b -> LRTree b
- class Graph gr => DynGraph (gr :: * -> * -> *) where
- buildGr :: DynGraph gr => [Context a b] -> gr a b
- insNode :: DynGraph gr => LNode a -> gr a b -> gr a b
- insNodes :: DynGraph gr => [LNode a] -> gr a b -> gr a b
- insEdge :: DynGraph gr => LEdge b -> gr a b -> gr a b
- insEdges :: DynGraph gr => [LEdge b] -> gr a b -> gr a b
- delNode :: Graph gr => Node -> gr a b -> gr a b
- delNodes :: Graph gr => [Node] -> gr a b -> gr a b
- delEdge :: DynGraph gr => Edge -> gr a b -> gr a b
- delEdges :: DynGraph gr => [Edge] -> gr a b -> gr a b
- delLEdge :: (DynGraph gr, Eq b) => LEdge b -> gr a b -> gr a b
- delAllLEdge :: (DynGraph gr, Eq b) => LEdge b -> gr a b -> gr a b
- gmap :: DynGraph gr => (Context a b -> Context c d) -> gr a b -> gr c d
- nmap :: DynGraph gr => (a -> c) -> gr a b -> gr c b
- emap :: DynGraph gr => (b -> c) -> gr a b -> gr a c
- nemap :: DynGraph gr => (a -> c) -> (b -> d) -> gr a b -> gr c d
- gfiltermap :: DynGraph gr => (Context a b -> MContext c d) -> gr a b -> gr c d
- nfilter :: DynGraph gr => (Node -> Bool) -> gr a b -> gr a b
- labnfilter :: Graph gr => (LNode a -> Bool) -> gr a b -> gr a b
- labfilter :: DynGraph gr => (a -> Bool) -> gr a b -> gr a b
- subgraph :: DynGraph gr => [Node] -> gr a b -> gr a b
- grev :: DynGraph gr => gr a b -> gr a b
- undir :: (Eq b, DynGraph gr) => gr a b -> gr a b
- unlab :: DynGraph gr => gr a b -> gr () ()
- efilter :: DynGraph gr => (LEdge b -> Bool) -> gr a b -> gr a b
- elfilter :: DynGraph gr => (b -> Bool) -> gr a b -> gr a b
- bcc :: DynGraph gr => gr a b -> [gr a b]
- prettify :: (DynGraph gr, Show a, Show b) => gr a b -> String
- prettyPrint :: (DynGraph gr, Show a, Show b) => gr a b -> IO ()
- trc :: DynGraph gr => gr a b -> gr a ()
- rc :: DynGraph gr => gr a b -> gr a ()
- tc :: DynGraph gr => gr a b -> gr a ()
- type Node = Int
- type LNode a = (Node, a)
- type UNode = LNode ()
- type Edge = (Node, Node)
- type LEdge b = (Node, Node, b)
- type UEdge = LEdge ()
- toEdge :: LEdge b -> Edge
- edgeLabel :: LEdge b -> b
- toLEdge :: Edge -> b -> LEdge b
- type Context a b = (Adj b, Node, a, Adj b)
- type MContext a b = Maybe (Context a b)
- type UContext = ([Node], Node, [Node])
- node' :: Context a b -> Node
- lab' :: Context a b -> a
- labNode' :: Context a b -> LNode a
- neighbors' :: Context a b -> [Node]
- lneighbors' :: Context a b -> Adj b
- suc' :: Context a b -> [Node]
- pre' :: Context a b -> [Node]
- lpre' :: Context a b -> [(Node, b)]
- lsuc' :: Context a b -> [(Node, b)]
- out' :: Context a b -> [LEdge b]
- inn' :: Context a b -> [LEdge b]
- outdeg' :: Context a b -> Int
- indeg' :: Context a b -> Int
- deg' :: Context a b -> Int
- type Decomp (g :: * -> * -> *) a b = (MContext a b, g a b)
- type GDecomp (g :: * -> * -> *) a b = (Context a b, g a b)
- type UDecomp g = (Maybe UContext, g)
- type Path = [Node]
- newtype LPath a = LP {}
- type UPath = [UNode]
- type RTree = [Path]
- type LRTree a = [LPath a]
- type Adj b = [(b, Node)]
- newtype OrdGr (gr :: * -> * -> *) a b = OrdGr {
- unOrdGr :: gr a b
Graph
Instances
Bifunctor Gr | |
Graph Gr | |
Defined in Data.Graph.Inductive.PatriciaTree | |
DynGraph Gr | |
(Eq a, Ord b) => Eq (Gr a b) | |
(Read a, Read b) => Read (Gr a b) | |
(Show a, Show b) => Show (Gr a b) | |
Generic (Gr a b) | |
(NFData a, NFData b) => NFData (Gr a b) | |
Defined in Data.Graph.Inductive.PatriciaTree | |
type Rep (Gr a b) | |
Defined in Data.Graph.Inductive.PatriciaTree |
Static graphs
class Graph (gr :: * -> * -> *) where #
An empty Graph
.
True if the given Graph
is empty.
match :: Node -> gr a b -> Decomp gr a b #
mkGraph :: [LNode a] -> [LEdge b] -> gr a b #
Create a Graph
from the list of LNode
s and LEdge
s.
For graphs that are also instances of DynGraph
, mkGraph ns
es
should be equivalent to (
.insEdges
es . insNodes
ns)
empty
labNodes :: gr a b -> [LNode a] #
matchAny :: gr a b -> GDecomp gr a b #
Instances
Graph Gr | |
Defined in Data.Graph.Inductive.PatriciaTree |
size :: Graph gr => gr a b -> Int #
The number of edges in the graph.
Note that this counts every edge found, so if you are representing an unordered graph by having each edge mirrored this will be incorrect.
If you created an unordered graph by either mirroring every edge
(including loops!) or using the undir
function in
Data.Graph.Inductive.Basic then you can safely halve the value
returned by this.
lneighbors :: Graph gr => gr a b -> Node -> Adj b #
Find the labelled links coming into or going from a Context
.
hasNeighbor :: Graph gr => gr a b -> Node -> Node -> Bool #
Checks if there is an undirected edge between two nodes.
hasNeighborAdj :: (Graph gr, Eq b) => gr a b -> Node -> (b, Node) -> Bool #
Checks if there is an undirected labelled edge between two nodes.
hasEdge :: Graph gr => gr a b -> Edge -> Bool #
Checks if there is a directed edge between two nodes.
hasLEdge :: (Graph gr, Eq b) => gr a b -> LEdge b -> Bool #
Checks if there is a labelled edge between two nodes.
:: Graph gr | |
=> (Context a b -> [Node]) | direction of fold |
-> (Context a b -> c -> d) | depth aggregation |
-> (Maybe d -> c -> c, c) | breadth/level aggregation |
-> [Node] | |
-> gr a b | |
-> c |
Directed graph fold.
ufold :: Graph gr => (Context a b -> c -> c) -> c -> gr a b -> c #
Fold a function over the graph by recursively calling match
.
Articulation points
ap :: Graph gr => gr a b -> [Node] #
Finds the articulation points for a connected undirected graph, by using the low numbers criteria:
a) The root node is an articulation point iff it has two or more children.
b) An non-root node v is an articulation point iff there exists at least one child w of v such that lowNumber(w) >= dfsNumber(v).
Breadth-first search
Depth-first search
:: Graph gr | |
=> CFun a b [Node] | Mapping from a node to its neighbours to be visited
as well. |
-> CFun a b c | Mapping from the |
-> [Node] | Nodes to be visited. |
-> gr a b | |
-> [c] |
xdffWith :: Graph gr => CFun a b [Node] -> CFun a b c -> [Node] -> gr a b -> [Tree c] #
Discard the graph part of the result of xdfWith
.
xdffWith d f vs g = fst (xdfWith d f vs g)
udfs :: Graph gr => [Node] -> gr a b -> [Node] #
Undirected depth-first search, obtained by following edges regardless of their direction.
udff :: Graph gr => [Node] -> gr a b -> [Tree Node] #
Undirected depth-first forest, obtained by following edges regardless of their direction.
rdff :: Graph gr => [Node] -> gr a b -> [Tree Node] #
Reverse depth-first forest, obtained by following predecessors.
topsort :: Graph gr => gr a b -> [Node] #
Topological sorting,
i.e. a list of Node
s so that if there's an edge between a source and a
target node, the source appears earlier in the result.
reachable :: Graph gr => Node -> gr a b -> [Node] #
Collection of nodes reachable from a starting point.
components :: Graph gr => gr a b -> [[Node]] #
Collection of connected components
noComponents :: Graph gr => gr a b -> Int #
Number of connected components
isConnected :: Graph gr => gr a b -> Bool #
Is the graph connected?
condensation :: Graph gr => gr a b -> gr [Node] () #
The condensation of the given graph, i.e., the graph of its strongly connected components.
Dominators
dom :: Graph gr => gr a b -> Node -> [(Node, [Node])] #
return the set of dominators of the nodes of a graph, given a root
iDom :: Graph gr => gr a b -> Node -> [(Node, Node)] #
return immediate dominators for each node of a graph, given a root
Voronoi diagrams
gvdIn :: (DynGraph gr, Real b) => [Node] -> gr a b -> Voronoi b #
Produce a shortest path forest (the roots of which are those nodes specified) from nodes in the graph to one of the root nodes (if possible).
gvdOut :: (Graph gr, Real b) => [Node] -> gr a b -> Voronoi b #
Produce a shortest path forest (the roots of which are those nodes specified) from nodes in the graph from one of the root nodes (if possible).
voronoiSet :: Node -> Voronoi b -> [Node] #
Return the nodes reachable to/from (depending on how the
Voronoi
was constructed) from the specified root node (if the
specified node is not one of the root nodes of the shortest path
forest, an empty list will be returned).
nearestNode :: Node -> Voronoi b -> Maybe Node #
Try to determine the nearest root node to the one specified in the shortest path forest.
nearestDist :: Node -> Voronoi b -> Maybe b #
The distance to the nearestNode
(if there is one) in the
shortest path forest.
nearestPath :: Node -> Voronoi b -> Maybe Path #
Try to construct a path to/from a specified node to one of the root nodes of the shortest path forest.
Independent node sets
indep :: DynGraph gr => gr a b -> [Node] #
Calculate the maximum independent node set of the specified graph.
indepSize :: DynGraph gr => gr a b -> ([Node], Int) #
The maximum independent node set along with its size.
Minimum spanning trees
Max flow
getRevEdges :: Num b => [Edge] -> [LEdge b] #
i 0 For each edge a--->b this function returns edge b--->a . i Edges a<--->b are ignored j
augmentGraph :: (DynGraph gr, Num b) => gr a b -> gr a (b, b, b) #
i 0 For each edge a--->b insert into graph the edge a<---b . Then change the i (i,0,i) label of every edge from a---->b to a------->b
where label (x,y,z)=(Max Capacity, Current flow, Residual capacity)
updAdjList :: Num b => Adj (b, b, b) -> Node -> b -> Bool -> Adj (b, b, b) #
Given a successor or predecessor list for node u
and given node v
, find
the label corresponding to edge (u,v)
and update the flow and
residual capacity of that edge's label. Then return the updated
list.
updateFlow :: (DynGraph gr, Num b) => Path -> b -> gr a (b, b, b) -> gr a (b, b, b) #
Update flow and residual capacity along augmenting path from s
to t
in
graph @G. For a path
[u,v,w,...] find the node
u in
G and
its successor and predecessor list, then update the corresponding
edges
(u,v) and
(v,u)@ on those lists by using the minimum
residual capacity of the path.
mfmg :: (DynGraph gr, Num b, Ord b) => gr a (b, b, b) -> Node -> Node -> gr a (b, b, b) #
Compute the flow from s
to t
on a graph whose edges are labeled with
(x,y,z)=(max capacity,current flow,residual capacity)
and all
edges are of the form a<---->b
. First compute the residual
graph, that is, delete those edges whose residual capacity is
zero. Then compute the shortest augmenting path from s
to t
,
and finally update the flow and residual capacity along that path
by using the minimum capacity of that path. Repeat this process
until no shortest path from s
to t
exist.
mf :: (DynGraph gr, Num b, Ord b) => gr a b -> Node -> Node -> gr a (b, b, b) #
Compute the flow from s to t on a graph whose edges are labeled with
x
, which is the max capacity and where not all edges need to be
of the form a<---->b. Return the flow as a grap whose edges are
labeled with (x,y,z)=(max capacity,current flow,residual
capacity) and all edges are of the form a<---->b
maxFlowgraph :: (DynGraph gr, Num b, Ord b) => gr a b -> Node -> Node -> gr a (b, b) #
Compute the maximum flow from s to t on a graph whose edges are labeled with x, which is the max capacity and where not all edges need to be of the form a<---->b. Return the flow as a graph whose edges are labeled with (y,x) = (current flow, max capacity).
maxFlow :: (DynGraph gr, Num b, Ord b) => gr a b -> Node -> Node -> b #
Compute the value of a maximumflow
Shortest path
spTree :: (Graph gr, Real b) => Node -> gr a b -> LRTree b #
Tree of shortest paths from a certain node to the rest of the (reachable) nodes.
Corresponds to dijkstra
applied to a heap in which the only known node is
the starting node, with a path of length 0 leading to it.
The edge labels of type b
are the edge weights; negative edge
weights are not supported.
:: (Graph gr, Real b) | |
=> Heap b (LPath b) | Initial heap of known paths and their lengths. |
-> gr a b | |
-> LRTree b |
Dijkstra's shortest path algorithm.
The edge labels of type b
are the edge weights; negative edge
weights are not supported.
Dynamic graphs
delAllLEdge :: (DynGraph gr, Eq b) => LEdge b -> gr a b -> gr a b #
Remove all edges equal to the one specified.
gmap :: DynGraph gr => (Context a b -> Context c d) -> gr a b -> gr c d #
Map a function over the graph by recursively calling match
.
nmap :: DynGraph gr => (a -> c) -> gr a b -> gr c b #
Map a function over the Node
labels in a graph.
emap :: DynGraph gr => (b -> c) -> gr a b -> gr a c #
Map a function over the Edge
labels in a graph.
gfiltermap :: DynGraph gr => (Context a b -> MContext c d) -> gr a b -> gr c d #
Build a graph out of the contexts for which the predicate is
satisfied by recursively calling match
.
nfilter :: DynGraph gr => (Node -> Bool) -> gr a b -> gr a b #
Returns the subgraph only containing the nodes which satisfy the given predicate.
labnfilter :: Graph gr => (LNode a -> Bool) -> gr a b -> gr a b #
Returns the subgraph only containing the labelled nodes which satisfy the given predicate.
labfilter :: DynGraph gr => (a -> Bool) -> gr a b -> gr a b #
Returns the subgraph only containing the nodes whose labels satisfy the given predicate.
subgraph :: DynGraph gr => [Node] -> gr a b -> gr a b #
Returns the subgraph induced by the supplied nodes.
undir :: (Eq b, DynGraph gr) => gr a b -> gr a b #
Make the graph undirected, i.e. for every edge from A to B, there exists an edge from B to A.
Bi-connected components
bcc :: DynGraph gr => gr a b -> [gr a b] #
Finds the bi-connected components of an undirected connected graph. It first finds the articulation points of the graph. Then it disconnects the graph on each articulation point and computes the connected components.
Pretty-printing
prettify :: (DynGraph gr, Show a, Show b) => gr a b -> String #
Pretty-print the graph. Note that this loses a lot of information, such as edge inverses, etc.
Transitive/reflexive closure
trc :: DynGraph gr => gr a b -> gr a () #
Finds the transitive, reflexive closure of a directed graph. Given a graph G=(V,E), its transitive closure is the graph: G* = (V,E*) where E*={(i,j): i,j in V and either i = j or there is a path from i to j in G}
rc :: DynGraph gr => gr a b -> gr a () #
Finds the reflexive closure of a directed graph. Given a graph G=(V,E), its transitive closure is the graph: G* = (V,Er union E) where Er = {(i,i): i in V}
tc :: DynGraph gr => gr a b -> gr a () #
Finds the transitive closure of a directed graph. Given a graph G=(V,E), its transitive closure is the graph: G* = (V,E*) where E*={(i,j): i,j in V and there is a path from i to j in G}
Misc. types
Node
Edge
Context
lneighbors' :: Context a b -> Adj b #
All labelled links coming into or going from a Context
.
Decomposition
type GDecomp (g :: * -> * -> *) a b = (Context a b, g a b) #
The same as Decomp
, only more sure of itself.
Path
Tree
Adj
OrdGr
newtype OrdGr (gr :: * -> * -> *) a b #
OrdGr comes equipped with an Ord instance, so that graphs can be used as e.g. Map keys.
Instances
(Graph gr, Ord a, Ord b) => Eq (OrdGr gr a b) | |
(Graph gr, Ord a, Ord b) => Ord (OrdGr gr a b) | |
Defined in Data.Graph.Inductive.Graph | |
Read (gr a b) => Read (OrdGr gr a b) | |
Show (gr a b) => Show (OrdGr gr a b) | |