| Copyright | (C) Frank Staals | 
|---|---|
| License | see the LICENSE file | 
| Maintainer | Frank Staals | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.PlanarGraph
Contents
Description
Data type for representing connected planar graphs
Synopsis
- data PlanarGraph s (w :: World) v e f
- embedding :: Getter (PlanarGraph s w v e f) (Permutation (Dart s))
- vertexData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v' e f) (Vector v) (Vector v')
- dartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e'))
- faceData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f') (Vector f) (Vector f')
- rawDartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector e) (Vector e')
- edgeData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e'))
- data World
- type family DualOf (sp :: World) where ...
- newtype Arc s = Arc {}
- data Direction
- rev :: Direction -> Direction
- data Dart s = Dart {- _arc :: !(Arc s)
- _direction :: !Direction
 
- arc :: forall s s. Lens (Dart s) (Dart s) (Arc s) (Arc s)
- direction :: forall s. Lens' (Dart s) Direction
- twin :: Dart s -> Dart s
- isPositive :: Dart s -> Bool
- newtype VertexId s (w :: World) = VertexId {- _unVertexId :: Int
 
- type VertexId' s = VertexId s Primal
- planarGraph :: [[(Dart s, e)]] -> PlanarGraph s Primal () e ()
- planarGraph' :: Permutation (Dart s) -> PlanarGraph s w () () ()
- fromAdjacencyLists :: forall s w h. (Foldable h, Functor h) => [(VertexId s w, h (VertexId s w))] -> PlanarGraph s w () () ()
- toAdjacencyLists :: PlanarGraph s w v e f -> [(VertexId s w, Vector (VertexId s w))]
- fromAdjRep :: proxy s -> Gr (Vtx v e) (Face f) -> PlanarGraph s Primal v e f
- toAdjRep :: PlanarGraph s w v e f -> Gr (Vtx v e) (Face f)
- numVertices :: PlanarGraph s w v e f -> Int
- numDarts :: PlanarGraph s w v e f -> Int
- numEdges :: PlanarGraph s w v e f -> Int
- numFaces :: PlanarGraph s w v e f -> Int
- darts' :: PlanarGraph s w v e f -> Vector (Dart s)
- darts :: PlanarGraph s w v e f -> Vector (Dart s, e)
- edges' :: PlanarGraph s w v e f -> Vector (Dart s)
- edges :: PlanarGraph s w v e f -> Vector (Dart s, e)
- vertices' :: PlanarGraph s w v e f -> Vector (VertexId s w)
- vertices :: PlanarGraph s w v e f -> Vector (VertexId s w, v)
- faces' :: PlanarGraph s w v e f -> Vector (FaceId s w)
- faces :: PlanarGraph s w v e f -> Vector (FaceId s w, f)
- traverseVertices :: Applicative m => (VertexId s w -> v -> m v') -> PlanarGraph s w v e f -> m (PlanarGraph s w v' e f)
- traverseDarts :: Applicative m => (Dart s -> e -> m e') -> PlanarGraph s w v e f -> m (PlanarGraph s w v e' f)
- traverseFaces :: Applicative m => (FaceId s w -> f -> m f') -> PlanarGraph s w v e f -> m (PlanarGraph s w v e f')
- tailOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w
- headOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w
- endPoints :: Dart s -> PlanarGraph s w v e f -> (VertexId s w, VertexId s w)
- incidentEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s)
- incomingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s)
- outgoingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s)
- neighboursOf :: VertexId s w -> PlanarGraph s w v e f -> Vector (VertexId s w)
- nextIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
- prevIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
- class HasDataOf g i where
- endPointDataOf :: Dart s -> Getter (PlanarGraph s w v e f) (v, v)
- endPointData :: Dart s -> PlanarGraph s w v e f -> (v, v)
- dual :: Getter (PlanarGraph s w v e f) (PlanarGraph s (DualOf w) f e v)
- newtype FaceId s w = FaceId {}
- type FaceId' s = FaceId s Primal
- leftFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w
- rightFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w
- boundaryDart :: FaceId s w -> PlanarGraph s w v e f -> Dart s
- boundary :: FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s)
- boundary' :: Dart s -> PlanarGraph s w v e f -> Vector (Dart s)
- boundaryVertices :: FaceId s w -> PlanarGraph s w v e f -> Vector (VertexId s w)
- nextEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
- prevEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
Documentation
>>>:{let dart i s = Dart (Arc i) (read s) (aA:aB:aC:aD:aE:aG:_) = take 6 [Arc 0..] myGraph :: PlanarGraph () Primal () String () myGraph = planarGraph [ [ (Dart aA Negative, "a-") , (Dart aC Positive, "c+") , (Dart aB Positive, "b+") , (Dart aA Positive, "a+") ] , [ (Dart aE Negative, "e-") , (Dart aB Negative, "b-") , (Dart aD Negative, "d-") , (Dart aG Positive, "g+") ] , [ (Dart aE Positive, "e+") , (Dart aD Positive, "d+") , (Dart aC Negative, "c-") ] , [ (Dart aG Negative, "g-") ] ] :}
This represents the following graph. Note that the graph is undirected, the arrows are just to indicate what the Positive direction of the darts is.

data PlanarGraph s (w :: World) v e f Source #
A *connected* Planar graph with bidirected edges. I.e. the edges (darts) are directed, however, for every directed edge, the edge in the oposite direction is also in the graph.
The types v, e, and f are the are the types of the data associated with the vertices, edges, and faces, respectively.
The orbits in the embedding are assumed to be in counterclockwise order. Therefore, every dart directly bounds the face to its right.
Instances
embedding :: Getter (PlanarGraph s w v e f) (Permutation (Dart s)) Source #
Get the embedding, reprsented as a permutation of the darts, of this graph.
vertexData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v' e f) (Vector v) (Vector v') Source #
dartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e')) Source #
lens to access the Dart Data
faceData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f') (Vector f) (Vector f') Source #
rawDartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector e) (Vector e') Source #
edgeData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e')) Source #
edgeData is just an alias for dartData
The world in which the graph lives
type family DualOf (sp :: World) where ... Source #
We can take the dual of a world. For the Primal this gives us the Dual, for the Dual this gives us the Primal.
Representing edges: Arcs and Darts
An Arc is a directed edge in a planar graph. The type s is used to tie this arc to a particular graph.
Instances
| Bounded (Arc s) Source # | |
| Enum (Arc s) Source # | |
| Defined in Data.PlanarGraph.Dart | |
| Eq (Arc s) Source # | |
| Ord (Arc s) Source # | |
| Show (Arc s) Source # | |
| Generic (Arc s) Source # | |
| Arbitrary (Arc s) Source # | |
| NFData (Arc s) Source # | |
| Defined in Data.PlanarGraph.Dart | |
| type Rep (Arc s) Source # | |
| Defined in Data.PlanarGraph.Dart | |
Darts have a direction which is either Positive or Negative (shown as +1 or -1, respectively).
Instances
| Bounded Direction Source # | |
| Enum Direction Source # | |
| Defined in Data.PlanarGraph.Dart Methods succ :: Direction -> Direction # pred :: Direction -> Direction # fromEnum :: Direction -> Int # enumFrom :: Direction -> [Direction] # enumFromThen :: Direction -> Direction -> [Direction] # enumFromTo :: Direction -> Direction -> [Direction] # enumFromThenTo :: Direction -> Direction -> Direction -> [Direction] # | |
| Eq Direction Source # | |
| Ord Direction Source # | |
| Read Direction Source # | |
| Show Direction Source # | |
| Generic Direction Source # | |
| Arbitrary Direction Source # | |
| NFData Direction Source # | |
| Defined in Data.PlanarGraph.Dart | |
| type Rep Direction Source # | |
A dart represents a bi-directed edge. I.e. a dart has a direction, however the dart of the oposite direction is always present in the planar graph as well.
Constructors
| Dart | |
| Fields 
 | |
Instances
| Enum (Dart s) Source # | |
| Defined in Data.PlanarGraph.Dart | |
| Eq (Dart s) Source # | |
| Ord (Dart s) Source # | |
| Show (Dart s) Source # | |
| Generic (Dart s) Source # | |
| Arbitrary (Dart s) Source # | |
| NFData (Dart s) Source # | |
| Defined in Data.PlanarGraph.Dart | |
| HasDataOf (PlanarGraph s w v e f) (Dart s) Source # | |
| Defined in Data.PlanarGraph.Core Methods dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) Source # | |
| type Rep (Dart s) Source # | |
| Defined in Data.PlanarGraph.Dart type Rep (Dart s) = D1 (MetaData "Dart" "Data.PlanarGraph.Dart" "hgeometry-combinatorial-0.9.0.0-6qy5VaQ7muxJuEfibyCL9S" False) (C1 (MetaCons "Dart" PrefixI True) (S1 (MetaSel (Just "_arc") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Arc s)) :*: S1 (MetaSel (Just "_direction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Direction))) | |
| type DataOf (PlanarGraph s w v e f) (Dart s) Source # | |
| Defined in Data.PlanarGraph.Core | |
twin :: Dart s -> Dart s Source #
Get the twin of this dart (edge)
>>>twin (dart 0 "+1")Dart (Arc 0) -1>>>twin (dart 0 "-1")Dart (Arc 0) +1
isPositive :: Dart s -> Bool Source #
test if a dart is Positive
Vertices
newtype VertexId s (w :: World) Source #
A vertex in a planar graph. A vertex is tied to a particular planar graph by the phantom type s, and to a particular world w.
Constructors
| VertexId | |
| Fields 
 | |
Instances
Building a planar graph
planarGraph :: [[(Dart s, e)]] -> PlanarGraph s Primal () e () Source #
Construct a planar graph, given the darts in cyclic order around each vertex.
running time: \(O(n)\).
planarGraph' :: Permutation (Dart s) -> PlanarGraph s w () () () Source #
Construct a planar graph
running time: \(O(n)\).
fromAdjacencyLists :: forall s w h. (Foldable h, Functor h) => [(VertexId s w, h (VertexId s w))] -> PlanarGraph s w () () () Source #
Construct a planar graph from a adjacency matrix. For every vertex, all vertices should be given in counter clockwise order.
pre: No self-loops, and no multi-edges
running time: \(O(n)\).
toAdjacencyLists :: PlanarGraph s w v e f -> [(VertexId s w, Vector (VertexId s w))] Source #
Produces the adjacencylists for all vertices in the graph. For every vertex, the adjacent vertices are given in counter clockwise order.
Note that in case a vertex u as a self loop, we have that this vertexId occurs twice in the list of neighbours, i.e.: u : [...,u,..,u,...]. Similarly, if there are multiple darts between a pair of edges they occur multiple times.
running time: \(O(n)\)
fromAdjRep :: proxy s -> Gr (Vtx v e) (Face f) -> PlanarGraph s Primal v e f Source #
Read a planar graph, given in JSON format into a planar graph. The adjacencylists should be in counter clockwise order.
running time: \(O(n)\)
toAdjRep :: PlanarGraph s w v e f -> Gr (Vtx v e) (Face f) Source #
Transforms the planar graph into a format taht can be easily converted into JSON format. For every vertex, the adjacent vertices are given in counter clockwise order.
See toAdjacencyLists for notes on how we handle self-loops.
running time: \(O(n)\)
Quering a planar graph
numVertices :: PlanarGraph s w v e f -> Int Source #
Get the number of vertices
>>>numVertices myGraph4
numDarts :: PlanarGraph s w v e f -> Int Source #
Get the number of Darts
>>>numDarts myGraph12
numEdges :: PlanarGraph s w v e f -> Int Source #
Get the number of Edges
>>>numEdges myGraph6
numFaces :: PlanarGraph s w v e f -> Int Source #
Get the number of faces
>>>numFaces myGraph4
darts :: PlanarGraph s w v e f -> Vector (Dart s, e) Source #
Get all darts together with their data
>>>mapM_ print $ darts myGraph(Dart (Arc 0) -1,"a-") (Dart (Arc 2) +1,"c+") (Dart (Arc 1) +1,"b+") (Dart (Arc 0) +1,"a+") (Dart (Arc 4) -1,"e-") (Dart (Arc 1) -1,"b-") (Dart (Arc 3) -1,"d-") (Dart (Arc 5) +1,"g+") (Dart (Arc 4) +1,"e+") (Dart (Arc 3) +1,"d+") (Dart (Arc 2) -1,"c-") (Dart (Arc 5) -1,"g-")
edges' :: PlanarGraph s w v e f -> Vector (Dart s) Source #
Enumerate all edges. We report only the Positive darts
edges :: PlanarGraph s w v e f -> Vector (Dart s, e) Source #
Enumerate all edges with their edge data. We report only the Positive darts.
>>>mapM_ print $ edges myGraph(Dart (Arc 2) +1,"c+") (Dart (Arc 1) +1,"b+") (Dart (Arc 0) +1,"a+") (Dart (Arc 5) +1,"g+") (Dart (Arc 4) +1,"e+") (Dart (Arc 3) +1,"d+")
vertices' :: PlanarGraph s w v e f -> Vector (VertexId s w) Source #
Enumerate all vertices
>>>vertices' myGraph[VertexId 0,VertexId 1,VertexId 2,VertexId 3]
vertices :: PlanarGraph s w v e f -> Vector (VertexId s w, v) Source #
Enumerate all vertices, together with their vertex data
faces' :: PlanarGraph s w v e f -> Vector (FaceId s w) Source #
Enumerate all faces in the planar graph
traverseVertices :: Applicative m => (VertexId s w -> v -> m v') -> PlanarGraph s w v e f -> m (PlanarGraph s w v' e f) Source #
Traverse the vertices
(^.vertexData) $ traverseVertices (i x -> Just (i,x)) myGraph Just [(VertexId 0,()),(VertexId 1,()),(VertexId 2,()),(VertexId 3,())] >>> traverseVertices (i x -> print (i,x)) myGraph >> pure () (VertexId 0,()) (VertexId 1,()) (VertexId 2,()) (VertexId 3,())
traverseDarts :: Applicative m => (Dart s -> e -> m e') -> PlanarGraph s w v e f -> m (PlanarGraph s w v e' f) Source #
Traverses the darts
>>>traverseDarts (\d x -> print (d,x)) myGraph >> pure ()(Dart (Arc 0) +1,"a+") (Dart (Arc 0) -1,"a-") (Dart (Arc 1) +1,"b+") (Dart (Arc 1) -1,"b-") (Dart (Arc 2) +1,"c+") (Dart (Arc 2) -1,"c-") (Dart (Arc 3) +1,"d+") (Dart (Arc 3) -1,"d-") (Dart (Arc 4) +1,"e+") (Dart (Arc 4) -1,"e-") (Dart (Arc 5) +1,"g+") (Dart (Arc 5) -1,"g-")
traverseFaces :: Applicative m => (FaceId s w -> f -> m f') -> PlanarGraph s w v e f -> m (PlanarGraph s w v e f') Source #
Traverses the faces
>>>traverseFaces (\i x -> print (i,x)) myGraph >> pure ()(FaceId 0,()) (FaceId 1,()) (FaceId 2,()) (FaceId 3,())
tailOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w Source #
The tail of a dart, i.e. the vertex this dart is leaving from
running time: \(O(1)\)
headOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w Source #
The vertex this dart is heading in to
running time: \(O(1)\)
endPoints :: Dart s -> PlanarGraph s w v e f -> (VertexId s w, VertexId s w) Source #
endPoints d g = (tailOf d g, headOf d g)
running time: \(O(1)\)
incidentEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #
All edges incident to vertex v, in counterclockwise order around v.
running time: \(O(k)\), where \(k\) is the output size
incomingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #
All incoming edges incident to vertex v, in counterclockwise order around v.
outgoingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #
All outgoing edges incident to vertex v, in counterclockwise order around v.
neighboursOf :: VertexId s w -> PlanarGraph s w v e f -> Vector (VertexId s w) Source #
Gets the neighbours of a particular vertex, in counterclockwise order around the vertex.
running time: \(O(k)\), where \(k\) is the output size
nextIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s Source #
Given a dart d that points into some vertex v, report the next dart in the cyclic order around v.
running time: \(O(1)\)
prevIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s Source #
Given a dart d that points into some vertex v, report the next dart in the cyclic order around v.
running time: \(O(1)\)
Associated Data
class HasDataOf g i where Source #
Methods
dataOf :: i -> Lens' g (DataOf g i) Source #
get the data associated with the value i.
running time: \(O(1)\) to read the data, \(O(n)\) to write it.
Instances
| HasDataOf (PlanarGraph s w v e f) (Dart s) Source # | |
| Defined in Data.PlanarGraph.Core Methods dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) Source # | |
| HasDataOf (PlanarGraph s w v e f) (FaceId s w) Source # | |
| Defined in Data.PlanarGraph.Core Methods dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) Source # | |
| HasDataOf (PlanarGraph s w v e f) (VertexId s w) Source # | |
| Defined in Data.PlanarGraph.Core Methods dataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (VertexId s w)) Source # | |
endPointDataOf :: Dart s -> Getter (PlanarGraph s w v e f) (v, v) Source #
Data corresponding to the endpoints of the dart
endPointData :: Dart s -> PlanarGraph s w v e f -> (v, v) Source #
Data corresponding to the endpoints of the dart
running time: \(O(1)\)
dual :: Getter (PlanarGraph s w v e f) (PlanarGraph s (DualOf w) f e v) Source #
Get the dual graph of this graph.
Faces
The type to reprsent FaceId's
Instances
| Enum (FaceId s w) Source # | |
| Defined in Data.PlanarGraph.Core Methods succ :: FaceId s w -> FaceId s w # pred :: FaceId s w -> FaceId s w # fromEnum :: FaceId s w -> Int # enumFrom :: FaceId s w -> [FaceId s w] # enumFromThen :: FaceId s w -> FaceId s w -> [FaceId s w] # enumFromTo :: FaceId s w -> FaceId s w -> [FaceId s w] # enumFromThenTo :: FaceId s w -> FaceId s w -> FaceId s w -> [FaceId s w] # | |
| Eq (FaceId s w) Source # | |
| Ord (FaceId s w) Source # | |
| Defined in Data.PlanarGraph.Core | |
| Show (FaceId s w) Source # | |
| ToJSON (FaceId s w) Source # | |
| Defined in Data.PlanarGraph.Core | |
| FromJSON (FaceId s w) Source # | |
| HasDataOf (PlanarGraph s w v e f) (FaceId s w) Source # | |
| Defined in Data.PlanarGraph.Core Methods dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) Source # | |
| type DataOf (PlanarGraph s w v e f) (FaceId s w) Source # | |
| Defined in Data.PlanarGraph.Core | |
leftFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w Source #
The face to the left of the dart
>>>leftFace (dart 1 "+1") myGraphFaceId 1>>>leftFace (dart 1 "-1") myGraphFaceId 2>>>leftFace (dart 2 "+1") myGraphFaceId 2>>>leftFace (dart 0 "+1") myGraphFaceId 0
running time: \(O(1)\).
rightFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w Source #
The face to the right of the dart
>>>rightFace (dart 1 "+1") myGraphFaceId 2>>>rightFace (dart 1 "-1") myGraphFaceId 1>>>rightFace (dart 2 "+1") myGraphFaceId 1>>>rightFace (dart 0 "+1") myGraphFaceId 1
running time: \(O(1)\).
boundaryDart :: FaceId s w -> PlanarGraph s w v e f -> Dart s Source #
Gets a dart bounding this face. I.e. a dart d such that the face lies to the right of the dart.
boundary :: FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #
The darts bounding this face, for internal faces in clockwise order, for the outer face in counter clockwise order.
running time: \(O(k)\), where \(k\) is the output size.
boundary' :: Dart s -> PlanarGraph s w v e f -> Vector (Dart s) Source #
Generates the darts incident to a face, starting with the given dart.
\(O(k)\), where \(k\) is the number of darts reported
boundaryVertices :: FaceId s w -> PlanarGraph s w v e f -> Vector (VertexId s w) Source #
The vertices bounding this face, for internal faces in clockwise order, for the outer face in counter clockwise order.
running time: \(O(k)\), where \(k\) is the output size.