planar-graph-1.0.0.0: A representation of planar graphs

MaintainerIvan.Miljenovic@gmail.com
Safe HaskellNone

Data.Graph.Planar

Contents

Description

Planar graphs are graphs that can be embedded onto a surface (i.e. they can be drawn on that surface without any edges crossing). As such, it is preferable to use a dedicated data structure for them that has information about how to achieve this embedding rather than a standard graph data structure.

(Please note however that this implementation has only been tested in terms of the embedding being on the unit sphere or disc; whether it works or not as-is on any other type of surface is unknown.)

The implementation here is loosely based upon that found in plantri by Gunnar Brinkmann and Brendan McKay: http://cs.anu.edu.au/~bdm/plantri/ (which is similar in concept to a doubly-connected edge list). The main differences are (if my understanding of the C code is correct):

  • plantri uses arrays (technically it uses one big array that it continually mutates); planar-graph uses Maps (thus making it easier to grow/shrink graphs).
  • plantri doesn't explicitly store nodes, just edges.
  • plantri utilises pointers, avoiding extra lookups.
  • Each edge stores in plantri has the face it is on, but only after they are explicitly calculated. In planar-graph, getFaces instead returns a Map for the faces.
  • plantri doesn't allow labels.

In particular, all edges - even undirected ones - are stored as two opposing directed half-edges. As such, care should be taken when dealing with edges. Also, the Node, Edge and Face identifiers are all abstract, and as such cannot be constructed directly.

All returned CLists represent values in a clockwise fashion (relative to the Node or Face in question).

Care should also be taken when dealing with more than one connected component, as there is no fixed embedding of multiple graphs on the same surface.

Synopsis

Documentation

data PlanarGraph n e Source

The overall planar graph data structure.

Instances

Functor (PlanarGraph n) 
(Eq n, Eq e) => Eq (PlanarGraph n e) 
(Read n, Read e) => Read (PlanarGraph n e) 
(Show n, Show e) => Show (PlanarGraph n e) 
(NFData n, NFData e) => NFData (PlanarGraph n e) 

Graph Information

Information about the nodes

data Node Source

An abstract representation of a node.

Instances

Eq Node 
Ord Node 
Read Node

Note that this instance of Read only works when directly applied to a String; it is supplied solely to assist with debugging.

Show Node

This instance of Show does not produce valid Haskell code; however, the Node type is abstract and not designed to be directly accessed.

NFData Node 

order :: PlanarGraph n e -> IntSource

The number of nodes in the graph (i.e. length . nodes).

hasNode :: PlanarGraph n e -> Node -> BoolSource

Is this node still in the graph?

nodes :: PlanarGraph n e -> [Node]Source

All the nodes in the graph (in some arbitrary order).

labNodes :: PlanarGraph n e -> [(Node, n)]Source

All the nodes and their labels in the graph (in some arbitrary order).

outgoingEdges :: PlanarGraph n e -> Node -> CList EdgeSource

Returns all outgoing edges for the specified node, travelling clockwise around the node. It assumes the node is indeed in the graph.

incomingEdges :: PlanarGraph n e -> Node -> CList EdgeSource

Returns all incoming edges for the specified node, travelling clockwise around the node. It assumes the node is indeed in the graph.

neighbours :: PlanarGraph n e -> Node -> CList NodeSource

The Nodes that are connected to this Node with an edge (in clockwise order).

nodeLabel :: PlanarGraph n e -> Node -> nSource

Returns the label for the specified node.

Information about the edges

To be able to embed the required order of edges around a particular Node, we can't rely on just having each node specify which other nodes are adjacent to it as with non-planar graph types; instead, we need a unique identifier (to be able to distinguish between multiple edges between two nodes). Furthermore, each edge has an inverse edge in the opposite direction. To be more precise, these can be referred to as half-edges.

Due to every edge having an inverse, a PlanarGraph implicitly undirected even though each edge is directed. As such, if you require a directed planar graph, use appropriate edge labels to denote whether an edge is the one you want or just its inverse.

Note the distinction between functions such as edges and halfEdges: the latter returns every single half-edge (i.e the inverse "edge" is also included) whereas the former only considers the primary edge. The distinction is made when adding edges to the graph: the first edge added in addEdge is considered the primary one.

To be more specific:

 length . edges == size
 length . halfEdges == 2 * size

data Edge Source

An abstract representation of an edge. Note that an explicit identifier is used for each edge rather than just using the two nodes that the edge connects. This is required in case more than one edge connects two nodes as we need to be able to distinguish them.

Instances

Eq Edge 
Ord Edge 
Read Edge

Note that this instance of Read only works when directly applied to a String; it is supplied solely to assist with debugging.

Show Edge

This instance of Show does not produce valid Haskell code; however, the Edge type is abstract and not designed to be directly accessed.

NFData Edge 

size :: PlanarGraph n e -> IntSource

The number of edges in the graph (i.e. length . edges).

hasEdge :: PlanarGraph n e -> Edge -> BoolSource

Is this edge still in the graph?

halfEdges :: PlanarGraph n e -> [Edge]Source

All the half-edges (thus also including inverses) in the graph (in some arbitrary order).

labHalfEdges :: PlanarGraph n e -> [(Edge, e)]Source

All the half-edges and their labels in the graph (in some arbitrary order).

halfEdgesBetween :: PlanarGraph n e -> [(Node, Node)]Source

A variant of halfEdges that returns the pair of nodes that form an edge rather than its unique identifier (again including inverse edges).

labHalfEdgesBetween :: PlanarGraph n e -> [((Node, Node), e)]Source

As with halfEdgesBetween, but including the labels.

edges :: PlanarGraph n e -> [Edge]Source

All the primary edges in the graph returned in arbitrary order.

labEdges :: PlanarGraph n e -> [(Edge, e)]Source

All the primary edges and their labels in the graph (in some arbitrary order).

edgesBetween :: PlanarGraph n e -> [(Node, Node)]Source

A variant of edges that returns the pair of nodes that form the primary edges.

labEdgesBetween :: PlanarGraph n e -> [((Node, Node), e)]Source

As with edgesBetween but including the labels.

fromNode :: PlanarGraph n e -> Edge -> NodeSource

The Node which this Edge is coming from.

toNode :: PlanarGraph n e -> Edge -> NodeSource

The Node which this Edge is going to.

prevEdge :: PlanarGraph n e -> Edge -> EdgeSource

The previous Edge going clockwise around the fromNode.

nextEdge :: PlanarGraph n e -> Edge -> EdgeSource

The next Edge going clockwise around the fromNode.

inverseEdge :: PlanarGraph n e -> Edge -> EdgeSource

The Edge that is an inverse to this one; i.e.:

 fromNode pg e == toNode pg $ inverseEdge pg e
 toNode pg e == fromNode pg $ inverseEdge pg e

edgeLabel :: PlanarGraph n e -> Edge -> eSource

Return the label for the specified edge.

Graph Manipulation

mergeGraphs :: PlanarGraph n e -> PlanarGraph n e -> (PlanarGraph n e, Node -> Node, Edge -> Edge)Source

mergeGraphs pg1 pg2 creates a disjoint union between pg1 and pg2 (i.e. puts them into the same graph but disconnected). This is used when they were created independently and thus probably have clashing Node and Edge values. For best performance, pg1 should be larger than pg2.

Along with the merged graph, two functions are returned: they respectively convert Node and Edge values from pg2 to those found in the merged graph.

Please note that these functions are partial and should only be used for the Node and Edge identifiers from pg2.

mergeAllGraphs :: [PlanarGraph n e] -> (PlanarGraph n e, [(Node -> Node, Edge -> Edge)])Source

Merge all the provided planar graphs together into one large graph, and provide translation functions for every graph in the list (the first pair in this list is just (id,id)).

See mergeGraphs for more information. For best performance, the graphs should be decreasing in size/order.

Graph Construction

empty :: PlanarGraph n eSource

Constructs an empty planar graph.

addNode :: n -> PlanarGraph n e -> (Node, PlanarGraph n e)Source

Add a node with the provided label to the graph, returning the updated graph and the node identifier.

addUNode :: Monoid n => PlanarGraph n e -> (Node, PlanarGraph n e)Source

As with addNode, but uses mempty as the label.

data EdgePos Source

Specification of where to place a new edge on a node in clockwise order.

Constructors

Anywhere

The new edge can be placed anywhere.

BeforeEdge !Edge

The new edge should be placed before the specified edge.

AfterEdge !Edge

The new edge should be placed after the specified edge.

addEdgeSource

Arguments

:: Node

The node f at which the main edge starts.

-> EdgePos

Positioning information at f.

-> Node

The node t at which the main edge ends.

-> EdgePos

Positioning information at t for the inverse edge (i.e. refers to outgoingEdges t).

-> e

The label for the main edge f -> t.

-> e

The label for the inverse edge t -> f.

-> PlanarGraph n e

The graph at which to add the edge.

-> ((Edge, Edge), PlanarGraph n e)

The main and inverse edge identifiers, and the updated graph.

Add an edge between two nodes f and t. In reality, since all edges are duplicated (see inverseEdge), two half-edges are inserted, and the identifiers of both are returned.

For functions such as edges, the first added half-edge is assumed to be the primary one.

If either node does not currently have any edges, then its corresponding EdgePos value is ignored. An EdgePos of Anywhere will place the edge before (i.e. anti-clockwise) of the last edge added to that node.

For example, let g refer to the following graph (where n1, etc. are both the labels and the variable names):

     ====                    ====
    ( n1 )                  ( n2 )
     ====                    ====





                             ====
                            ( n3 )
                             ====

We can add an edge between n1 and n2 (using Anywhere as the EdgePos since there are currently no edges on either node):

 ((e1,e2),g') = addEdge n1 Anywhere n2 Anywhere "e1" "e2" g

This will result in the following graph:

                  e2
     ====  <---------------  ====
    ( n1 )                  ( n2 )
     ====  --------------->  ====
                  e1




                             ====
                            ( n3 )
                             ====

If we want to add edges between n2 and n3, we have three options for the location on n2:

  • Use Anywhere: since there is only one other edge, it makes no difference in terms of the embedding where the second edge goes.
  • Put the new edge BeforeEdge e2 (going clockwise around n2).
  • Put the new edge AfterEdge e2 (going clockwise around n2).

Since n2 currently only has one edge, all three EdgePos values will result in the same graph, so we can arbitrarily pick one:

 ((e3,e4),g'') = addEdge n2 (BeforeEdge e2) n3 Anywhere "e3" "e4" g'

However, with more edges care must be taken on which EdgePos value is used. The resulting graph is:

                  e2
     ====  <---------------  ====
    ( n1 )                  ( n2 )
     ====  --------------->  ====
                  e1         |  ^
                             |  |
                          e3 |  | e4
                             |  |
                             v  |
                             ====
                            ( n3 )
                             ====

The same graph (up to the actual Edge values; so it won't satisfy ==) would have been obtained with:

 ((e4,e3), g'') = addEdge n3 Anywhere n2 (BeforeEdge e2) "e4" "e3" g'

(Note, however, that now edges will return e4 rather than e3 as it is considered to be the primary edge.)

addEdgeUndirected :: Node -> EdgePos -> Node -> EdgePos -> e -> PlanarGraph n e -> (Edge, PlanarGraph n e)Source

As with addEdge, but the edges are meant to be undirected so use the same label for both.

addUEdge :: Monoid e => Node -> EdgePos -> Node -> EdgePos -> PlanarGraph n e -> ((Edge, Edge), PlanarGraph n e)Source

As with addEdge, but both labels are set to mempty.

Graph Deconstruction

isEmpty :: PlanarGraph n e -> BoolSource

Determines if the graph is empty.

deleteNode :: Node -> PlanarGraph n e -> PlanarGraph n eSource

Delete the node and all adjacent edges from the graph.

deleteEdge :: Edge -> PlanarGraph n e -> PlanarGraph n eSource

Delete the edge and its inverse from the graph.

contractEdge :: Edge -> (n -> n -> n) -> PlanarGraph n e -> PlanarGraph n eSource

Merges the two nodes adjoined by this edge, and delete all edges between them. The provided function is to decide what the label for the resulting node should be (if the edge goes from f to t, then the function is fLabel -> tLabel -> newLabel). The Node value for the merged node is fromNode pg e.

Note that this may result in multiple edges between the new node and another node if it is adjacent to both nodes being merged.

Other

unlabel :: PlanarGraph n e -> PlanarGraph () ()Source

Remove all labels from this graph.

mapNodes :: (n -> n') -> PlanarGraph n e -> PlanarGraph n' eSource

Apply a mapping function over the node labels.

adjustNodeLabel :: (n -> n) -> Node -> PlanarGraph n e -> PlanarGraph n eSource

Apply a function to the label of the specified node.

setNodeLabel :: n -> Node -> PlanarGraph n e -> PlanarGraph n eSource

Set the label of the specified node.

mapEdges :: (e -> e') -> PlanarGraph n e -> PlanarGraph n e'Source

Apply a mapping function over the edge labels.

adjustEdgeLabel :: (e -> e) -> Edge -> PlanarGraph n e -> PlanarGraph n eSource

Apply a function to the label of the specified edge.

setEdgeLabel :: e -> Edge -> PlanarGraph n e -> PlanarGraph n eSource

Set the label of the specified edge.

Graph traversal

traverse :: Traversal -> PlanarGraph n e -> Maybe Edge -> [GraphTraversal]Source

Traverse through a graph, and return each connected component found. If an edge is specified, start with that edge and then for subsequent components (if there are any) arbitrarily pick edges to start with; if no edge is provided than start at an arbitrary edge.

connectedComponents :: PlanarGraph n e -> [(PlanarGraph n e, (Node -> Node, Edge -> Edge))]Source

Use a breadthFirst traversal to find all the connected components. The node and edge identifiers for each component are re-numbered.

renumber :: Traversal -> PlanarGraph n e -> Maybe Edge -> (PlanarGraph n e, (Node -> Node, Edge -> Edge))Source

Perform a re-numbering of the identifiers in this graph using the specified traversal and optionally starting from a specified edge.

If there is only one connected component in the graph and the same edge is specified each time (relative to the location in the graph), then the re-numbering is canonical: that is, it can be used to compare whether two graphs constructed via separate paths (and thus using different identifiers) are indeed the same.

Controlling traversal

data Traversal Source

Different ways of traversing through a graph.

To assist in visualising how the traversals differ, sample traversals will be provided for the following graph:

                                =====
                               (  1  )
                                =====
                                  |
                                a |
                                  |
                                =====
                               (  2  )
                                =====
                                / | \
                        b      /  |  \      c
                 /-------------   |   -------------\
                /                 |                 \
             =====              d |                =====
            (  3  )               |               (  5  )
             =====              =====              =====
               |               (  4  )             /   \
               |                =====             /     \
               |                  |              /       \
             e |                f |           g /         \ h
               |                  |            /           \
               |                  |           |             |
               |                 /            |             |
               |                /             |             |
             =====             /           =====           =====
            (  6  )-----------/           (  7  )         (  8  )
             =====                         =====           =====

Each traversal shall start at the edge labelled a: note that whenever an edge is traversed, it immediately also traverses its inverse.

In particular, note where the node labelled 4 and its two adjacent edges are found.

breadthFirst :: TraversalSource

A breadth-first traversal on the sample graph would visit the nodes and edges in the following order:

nodes:
1 2 5 4 3 8 7 6
edges:
a c d b h g f e

If spanningTraversal was used, then the edge e wouldn't be traversed; if antiClockwiseTraversal was also used, then instead f wouldn't be traversed.

depthFirst :: TraversalSource

A depth-first traversal on the sample graph would visit the nodes and edges in the following order:

nodes:
1 2 5 8 7 4 6 3
edges:
a c h g d f e b

If spanningTraversal was used, then the edge b wouldn't be traversed; if antiClockwiseTraversal was also used then instead d wouldn't be traversed.

antiClockwiseTraversal :: Traversal -> TraversalSource

By default, the traversals do so in a clockwise fashion, just as the outgoing edges are defined for each node. This lets you specify that an anti-clockwise traversal should be done instead.

This is not computationally any more expensive than clockwise traversals.

spanningTraversal :: Traversal -> TraversalSource

Perform a traversal suitable for a spanning tree. In this case, edges that reach a node that has already been visited won't be traversed.

This does make getting each connected component more expensive.

Results of traversing

type GraphTraversal = (TraversedValues Node, TraversedValues Edge)Source

Specify part of a graph found by traversing it. For nodes, visited == fromList . toList . traversed; the same is true for edges except when spanningTraversal is used. In that case, traversed may contain a sub-set of visited (and if they aren't equal, anyMissing will be True.).

data TraversedValues a Source

The values found whilst traversing. See GraphTraversal for more specific information.

visited :: TraversedValues a -> Set aSource

All values encountered.

traversed :: TraversedValues a -> Seq aSource

The order in which values are encountered.

anyMissing :: TraversedValues a -> BoolSource

Did we skip any edges?

mergeGraphTraversals :: [GraphTraversal] -> GraphTraversalSource

Merge the results from traverse into one traversal (i.e. you don't care about individual components).

Graph duals and faces

The dual of a planar graph G is another planar graph H such that H has an node for every face in G, and an edge between two nodes if the corresponding faces in G are adjacent. For example, the graph (drawn as an undirected graph for simplicity):

                o---------o---------o
                |         |         |
                |   f1    |   f2    |
                |         |         |
                o---------o---------o
                 \                 /
                  \               /
                   \     f3      /
                    \           /
        outer        \         /
         face         \       /
                       \     /
                        \   /
                         \ /
                          o

has a dual graph of:

                 ......
            .....      .....
         ...                ..
       ..      ......        ..
      .       .      .         .
     .       .     =====     ===== .....
     .      .   ..( f1  )...( f2  )    ....
     .     .   ..  =====     =====         ..
     .    .   .       .      .               .
     .   .   .          .   .                 .
     .  =====           =====                  .
     . /     \.........( f3  )...               .
      /       \         =====   ....             .
      | outer |                     .            .
      \  face /                      .           .
       \     / .                      .          .
        =====   .                     .          .
           .      .                  .           .
            .       .               .           .
              .       .............            .
                .                             .
                  ..                         .
                     .                      .
                       .               ....
                        ................

A dual graph is a planar multigraph: it will still be a planar graph, but may have loops and multiple edges. However, the dual of a dual graph will be the original graph (though no guarantees are made that g == makeDual (makeDual g) due to differing Node and Edge values).

Note that the functions here assume that the graph is connected; in effect multiple connected components will be treated individually with no notion of relative embeddings.

data Face Source

An abstract representation of a face.

Instances

Eq Face 
Ord Face 
Read Face

Note that this instance of Read only works when directly applied to a String; it is supplied solely to assist with debugging.

Show Face

This instance of Show does not produce valid Haskell code; however, the Face type is abstract and not designed to be directly accessed.

NFData Face 

type FaceMap = Map Face FaceInfoSource

Information about the faces in a planar graph.

data FaceInfo Source

Information about a particular Face.

faceNodes :: FaceInfo -> CList NodeSource

The Nodes that make up the face.

edgeCrossings :: FaceInfo -> CList ((Edge, Edge), Face)Source

The Edges that make up the face, its inverse and the Face on the other side of that Edge.

faceEdges :: FaceInfo -> CList EdgeSource

The Edges that make up the face.

adjoiningFaces :: FaceInfo -> CList FaceSource

The adjoining Faces. Will have repeats if the Faces are adjacent over more than one Edge.

getFaces :: PlanarGraph n e -> FaceMapSource

Finds all faces in the planar graph. A face is defined by traversing along the right-hand-side of edges, e.g.:

           o----------------------------->o
           ^..............................|
           |..............................|
           |..............FACE............|
           |..............................|
           |..............................v
           o<-----------------------------o

(with the inverse edges all being on the outside of the edges shown).

getFace :: PlanarGraph n e -> Edge -> ([Node], [Edge])Source

Returns all nodes and edges in the same face as the provided edge (including that edge); assumes the edge is part of the graph.

Constructing the dual

makeDual :: PlanarGraph n e -> PlanarGraph () ()Source

Create the dual of a planar graph. If actual node and edge labels are required, use toDual.

toDual :: (Face -> n) -> (Face -> Edge -> Face -> e) -> FaceMap -> ((Face -> Node, Edge -> Edge), PlanarGraph n e)Source

Create the planar graph corresponding to the dual of the face relationships. The usage of FaceMap rather than PlanarGraph is to allow you to use the FaceMap for constructing the label-creation functions if you so wish.

The function eLabel for edge labels takes the Face that the edge comes from, the Edge belonging to that Face that it is crossing and then the Face that it is going to. For example:

                  ....              ....>
                      ...> =====....
                          (#####)
                           =====
                            | ^  e2
                            | |
                            | |
              face1         | |      face2
                            | |
                            | |
                            | |
                        e1  v |
                           =====
                          (#####)
                        ...===== <..
                    <...            ....
                                        ...

Here, the edge in the dual graph going from face1 to face2 will have a label of "eLabel face1 e1 face2", and the edge going from face2 to face1 will have a label of "eLabel face2 e2 face1".

The returned functions are a mapping from the faces in the FaceMap to the nodes in the dual graph, and the edges in the original graph to the edge in the dual that crosses it (e.g. in the above diagram, e1 will have a mapping to the edge from face1 to face2).

Isomorphism testing

canonicalExampleBy :: (Ord n, Ord e) => (PlanarGraph n e -> [Edge]) -> Edge -> PlanarGraph n e -> BoolSource

Determine if this graph is the canonical representative of the isomorphic class (defined as such by having a breadth-first serialisation via serialiseBFS that is <= any other such serialisation).

The function specifies all possible starting edges for the traversal (it is safe to leave the specified edge being returned by this function). If there are no known unique aspects of this graph that could be used to minimise "uniqueness", then use the halfEdges function (note: you probably do not want to use edges if the graph is undirected).

Note that this really only makes sense for graphs of type PlanarGraph () (), unless you are sure that the labels won't affect the comparisons.

onlyCanonicalExamples :: (Ord n, Ord e) => (PlanarGraph n e -> [Edge]) -> [(Edge, PlanarGraph n e)] -> [(Edge, PlanarGraph n e)]Source

Filter out all those graphs for which canonicalExampleBy isn't True.

For this function to be correct, no two (Edge, PlanarGraph n e) pairs should have the same result from serialiseBFS. For example, consider the following graph g:

                 e1
      ===== <--------- =====
     (     )--------->(     )
      =====          / =====
      | ^           / /| | ^
      | |          / /   | |
      | |         / /    | |
      | |        / /     | |
      | |       / /      | |
      | |      / /       | |
      | |     / /        | |
      | |    / /         | |
      | |   / /          | |
      v | |/ /           v |
      ===== /          =====
     (     )<---------(     )
      ===== ---------> =====
                 e2

Then onlyCanonicalExamples halfEdges [(e1,g), (e2,g)] will return both graphs, even though they represent the same graph.

Note that this really only makes sense for graphs of type PlanarGraph () (), unless you are sure that the labels won't affect the comparisons.

Alternate representations

Serialisation

Serialisation support can be found here to aid in converting a PlanarGraph to alternate formats. Care should be taken when constructing the SerialisedGraph, and these functions should not be abused just to edit an existing PlanarGraph.

type SerialisedGraph n e = [(Word, n, [(Word, Word, e, Word)])]Source

The definition of a more compact, serialised form of a planar graph. The various fields correspond to:

 [( node index
  , node label
  , [( edge index
     , node index that this edge points to
     , edge label
     , inverse edge index
    )]
 )]

The list of edges should be in clockwise order around the node.

Note that there will be twice as many edges lists as the size; that's because each edge is listed twice.

serialise :: PlanarGraph n e -> SerialisedGraph n eSource

Create the serialised form of this graph.

deserialise :: SerialisedGraph n e -> PlanarGraph n eSource

Creates the graph from its serialised form. Assumes that the graph is valid.

serialTraversal :: PlanarGraph n e -> ((Int, Int), SerialisedGraph n e)Source

An alias for serialiseBFS with no specified edge. Also added are the order and size of the graph.

This function is mainly intended for use by the Data.Graph.Planar.Serialisation module.

serialiseBFS :: PlanarGraph n e -> Maybe Edge -> SerialisedGraph n eSource

Perform a breadth-first traversal serialisation of the provided graph. If an edge is provided, then it is the first edge and its fromNode is the first node; if no edge is provided then an arbitrary edge is chosen.

Up to the choice of starting edge, the returned SerialisedGraph should be unique no matter how the graph was constructed.

Note that only one connected component is used: this is because if there is more than one component then the serialisation is not unique (due to how to choose the ordering of the components).

Pretty-Printing

prettify :: (Show n, Show e) => PlanarGraph n e -> StringSource

Pretty-print the graph. Note that this loses a lot of information, such as edge inverses, etc.

prettyPrint :: (Show n, Show e) => PlanarGraph n e -> IO ()Source

Pretty-print the graph to stdout.